{-# 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.WellArchitected.Types.CheckDetail
-- 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.WellArchitected.Types.CheckDetail where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.WellArchitected.Types.CheckFailureReason
import Amazonka.WellArchitected.Types.CheckProvider
import Amazonka.WellArchitected.Types.CheckStatus

-- | Account details for a Well-Architected best practice in relation to
-- Trusted Advisor checks.
--
-- /See:/ 'newCheckDetail' smart constructor.
data CheckDetail = CheckDetail'
  { CheckDetail -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text,
    CheckDetail -> Maybe Text
choiceId :: Prelude.Maybe Prelude.Text,
    -- | Trusted Advisor check description.
    CheckDetail -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Count of flagged resources associated to the check.
    CheckDetail -> Maybe Natural
flaggedResources :: Prelude.Maybe Prelude.Natural,
    -- | Trusted Advisor check ID.
    CheckDetail -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | Well-Architected Lens ARN associated to the check.
    CheckDetail -> Maybe Text
lensArn :: Prelude.Maybe Prelude.Text,
    -- | Trusted Advisor check name.
    CheckDetail -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    CheckDetail -> Maybe Text
pillarId :: Prelude.Maybe Prelude.Text,
    -- | Provider of the check related to the best practice.
    CheckDetail -> Maybe CheckProvider
provider :: Prelude.Maybe CheckProvider,
    CheckDetail -> Maybe Text
questionId :: Prelude.Maybe Prelude.Text,
    -- | Reason associated to the check.
    CheckDetail -> Maybe CheckFailureReason
reason :: Prelude.Maybe CheckFailureReason,
    -- | Status associated to the check.
    CheckDetail -> Maybe CheckStatus
status :: Prelude.Maybe CheckStatus,
    CheckDetail -> Maybe POSIX
updatedAt :: Prelude.Maybe Data.POSIX
  }
  deriving (CheckDetail -> CheckDetail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckDetail -> CheckDetail -> Bool
$c/= :: CheckDetail -> CheckDetail -> Bool
== :: CheckDetail -> CheckDetail -> Bool
$c== :: CheckDetail -> CheckDetail -> Bool
Prelude.Eq, ReadPrec [CheckDetail]
ReadPrec CheckDetail
Int -> ReadS CheckDetail
ReadS [CheckDetail]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CheckDetail]
$creadListPrec :: ReadPrec [CheckDetail]
readPrec :: ReadPrec CheckDetail
$creadPrec :: ReadPrec CheckDetail
readList :: ReadS [CheckDetail]
$creadList :: ReadS [CheckDetail]
readsPrec :: Int -> ReadS CheckDetail
$creadsPrec :: Int -> ReadS CheckDetail
Prelude.Read, Int -> CheckDetail -> ShowS
[CheckDetail] -> ShowS
CheckDetail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckDetail] -> ShowS
$cshowList :: [CheckDetail] -> ShowS
show :: CheckDetail -> String
$cshow :: CheckDetail -> String
showsPrec :: Int -> CheckDetail -> ShowS
$cshowsPrec :: Int -> CheckDetail -> ShowS
Prelude.Show, forall x. Rep CheckDetail x -> CheckDetail
forall x. CheckDetail -> Rep CheckDetail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CheckDetail x -> CheckDetail
$cfrom :: forall x. CheckDetail -> Rep CheckDetail x
Prelude.Generic)

-- |
-- Create a value of 'CheckDetail' 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:
--
-- 'accountId', 'checkDetail_accountId' - Undocumented member.
--
-- 'choiceId', 'checkDetail_choiceId' - Undocumented member.
--
-- 'description', 'checkDetail_description' - Trusted Advisor check description.
--
-- 'flaggedResources', 'checkDetail_flaggedResources' - Count of flagged resources associated to the check.
--
-- 'id', 'checkDetail_id' - Trusted Advisor check ID.
--
-- 'lensArn', 'checkDetail_lensArn' - Well-Architected Lens ARN associated to the check.
--
-- 'name', 'checkDetail_name' - Trusted Advisor check name.
--
-- 'pillarId', 'checkDetail_pillarId' - Undocumented member.
--
-- 'provider', 'checkDetail_provider' - Provider of the check related to the best practice.
--
-- 'questionId', 'checkDetail_questionId' - Undocumented member.
--
-- 'reason', 'checkDetail_reason' - Reason associated to the check.
--
-- 'status', 'checkDetail_status' - Status associated to the check.
--
-- 'updatedAt', 'checkDetail_updatedAt' - Undocumented member.
newCheckDetail ::
  CheckDetail
newCheckDetail :: CheckDetail
newCheckDetail =
  CheckDetail'
    { $sel:accountId:CheckDetail' :: Maybe Text
accountId = forall a. Maybe a
Prelude.Nothing,
      $sel:choiceId:CheckDetail' :: Maybe Text
choiceId = forall a. Maybe a
Prelude.Nothing,
      $sel:description:CheckDetail' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:flaggedResources:CheckDetail' :: Maybe Natural
flaggedResources = forall a. Maybe a
Prelude.Nothing,
      $sel:id:CheckDetail' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:lensArn:CheckDetail' :: Maybe Text
lensArn = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CheckDetail' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:pillarId:CheckDetail' :: Maybe Text
pillarId = forall a. Maybe a
Prelude.Nothing,
      $sel:provider:CheckDetail' :: Maybe CheckProvider
provider = forall a. Maybe a
Prelude.Nothing,
      $sel:questionId:CheckDetail' :: Maybe Text
questionId = forall a. Maybe a
Prelude.Nothing,
      $sel:reason:CheckDetail' :: Maybe CheckFailureReason
reason = forall a. Maybe a
Prelude.Nothing,
      $sel:status:CheckDetail' :: Maybe CheckStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:updatedAt:CheckDetail' :: Maybe POSIX
updatedAt = forall a. Maybe a
Prelude.Nothing
    }

-- | Undocumented member.
checkDetail_accountId :: Lens.Lens' CheckDetail (Prelude.Maybe Prelude.Text)
checkDetail_accountId :: Lens' CheckDetail (Maybe Text)
checkDetail_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe Text
accountId :: Maybe Text
$sel:accountId:CheckDetail' :: CheckDetail -> Maybe Text
accountId} -> Maybe Text
accountId) (\s :: CheckDetail
s@CheckDetail' {} Maybe Text
a -> CheckDetail
s {$sel:accountId:CheckDetail' :: Maybe Text
accountId = Maybe Text
a} :: CheckDetail)

-- | Undocumented member.
checkDetail_choiceId :: Lens.Lens' CheckDetail (Prelude.Maybe Prelude.Text)
checkDetail_choiceId :: Lens' CheckDetail (Maybe Text)
checkDetail_choiceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe Text
choiceId :: Maybe Text
$sel:choiceId:CheckDetail' :: CheckDetail -> Maybe Text
choiceId} -> Maybe Text
choiceId) (\s :: CheckDetail
s@CheckDetail' {} Maybe Text
a -> CheckDetail
s {$sel:choiceId:CheckDetail' :: Maybe Text
choiceId = Maybe Text
a} :: CheckDetail)

-- | Trusted Advisor check description.
checkDetail_description :: Lens.Lens' CheckDetail (Prelude.Maybe Prelude.Text)
checkDetail_description :: Lens' CheckDetail (Maybe Text)
checkDetail_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe Text
description :: Maybe Text
$sel:description:CheckDetail' :: CheckDetail -> Maybe Text
description} -> Maybe Text
description) (\s :: CheckDetail
s@CheckDetail' {} Maybe Text
a -> CheckDetail
s {$sel:description:CheckDetail' :: Maybe Text
description = Maybe Text
a} :: CheckDetail)

-- | Count of flagged resources associated to the check.
checkDetail_flaggedResources :: Lens.Lens' CheckDetail (Prelude.Maybe Prelude.Natural)
checkDetail_flaggedResources :: Lens' CheckDetail (Maybe Natural)
checkDetail_flaggedResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe Natural
flaggedResources :: Maybe Natural
$sel:flaggedResources:CheckDetail' :: CheckDetail -> Maybe Natural
flaggedResources} -> Maybe Natural
flaggedResources) (\s :: CheckDetail
s@CheckDetail' {} Maybe Natural
a -> CheckDetail
s {$sel:flaggedResources:CheckDetail' :: Maybe Natural
flaggedResources = Maybe Natural
a} :: CheckDetail)

-- | Trusted Advisor check ID.
checkDetail_id :: Lens.Lens' CheckDetail (Prelude.Maybe Prelude.Text)
checkDetail_id :: Lens' CheckDetail (Maybe Text)
checkDetail_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe Text
id :: Maybe Text
$sel:id:CheckDetail' :: CheckDetail -> Maybe Text
id} -> Maybe Text
id) (\s :: CheckDetail
s@CheckDetail' {} Maybe Text
a -> CheckDetail
s {$sel:id:CheckDetail' :: Maybe Text
id = Maybe Text
a} :: CheckDetail)

-- | Well-Architected Lens ARN associated to the check.
checkDetail_lensArn :: Lens.Lens' CheckDetail (Prelude.Maybe Prelude.Text)
checkDetail_lensArn :: Lens' CheckDetail (Maybe Text)
checkDetail_lensArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe Text
lensArn :: Maybe Text
$sel:lensArn:CheckDetail' :: CheckDetail -> Maybe Text
lensArn} -> Maybe Text
lensArn) (\s :: CheckDetail
s@CheckDetail' {} Maybe Text
a -> CheckDetail
s {$sel:lensArn:CheckDetail' :: Maybe Text
lensArn = Maybe Text
a} :: CheckDetail)

-- | Trusted Advisor check name.
checkDetail_name :: Lens.Lens' CheckDetail (Prelude.Maybe Prelude.Text)
checkDetail_name :: Lens' CheckDetail (Maybe Text)
checkDetail_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe Text
name :: Maybe Text
$sel:name:CheckDetail' :: CheckDetail -> Maybe Text
name} -> Maybe Text
name) (\s :: CheckDetail
s@CheckDetail' {} Maybe Text
a -> CheckDetail
s {$sel:name:CheckDetail' :: Maybe Text
name = Maybe Text
a} :: CheckDetail)

-- | Undocumented member.
checkDetail_pillarId :: Lens.Lens' CheckDetail (Prelude.Maybe Prelude.Text)
checkDetail_pillarId :: Lens' CheckDetail (Maybe Text)
checkDetail_pillarId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe Text
pillarId :: Maybe Text
$sel:pillarId:CheckDetail' :: CheckDetail -> Maybe Text
pillarId} -> Maybe Text
pillarId) (\s :: CheckDetail
s@CheckDetail' {} Maybe Text
a -> CheckDetail
s {$sel:pillarId:CheckDetail' :: Maybe Text
pillarId = Maybe Text
a} :: CheckDetail)

-- | Provider of the check related to the best practice.
checkDetail_provider :: Lens.Lens' CheckDetail (Prelude.Maybe CheckProvider)
checkDetail_provider :: Lens' CheckDetail (Maybe CheckProvider)
checkDetail_provider = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe CheckProvider
provider :: Maybe CheckProvider
$sel:provider:CheckDetail' :: CheckDetail -> Maybe CheckProvider
provider} -> Maybe CheckProvider
provider) (\s :: CheckDetail
s@CheckDetail' {} Maybe CheckProvider
a -> CheckDetail
s {$sel:provider:CheckDetail' :: Maybe CheckProvider
provider = Maybe CheckProvider
a} :: CheckDetail)

-- | Undocumented member.
checkDetail_questionId :: Lens.Lens' CheckDetail (Prelude.Maybe Prelude.Text)
checkDetail_questionId :: Lens' CheckDetail (Maybe Text)
checkDetail_questionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe Text
questionId :: Maybe Text
$sel:questionId:CheckDetail' :: CheckDetail -> Maybe Text
questionId} -> Maybe Text
questionId) (\s :: CheckDetail
s@CheckDetail' {} Maybe Text
a -> CheckDetail
s {$sel:questionId:CheckDetail' :: Maybe Text
questionId = Maybe Text
a} :: CheckDetail)

-- | Reason associated to the check.
checkDetail_reason :: Lens.Lens' CheckDetail (Prelude.Maybe CheckFailureReason)
checkDetail_reason :: Lens' CheckDetail (Maybe CheckFailureReason)
checkDetail_reason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe CheckFailureReason
reason :: Maybe CheckFailureReason
$sel:reason:CheckDetail' :: CheckDetail -> Maybe CheckFailureReason
reason} -> Maybe CheckFailureReason
reason) (\s :: CheckDetail
s@CheckDetail' {} Maybe CheckFailureReason
a -> CheckDetail
s {$sel:reason:CheckDetail' :: Maybe CheckFailureReason
reason = Maybe CheckFailureReason
a} :: CheckDetail)

-- | Status associated to the check.
checkDetail_status :: Lens.Lens' CheckDetail (Prelude.Maybe CheckStatus)
checkDetail_status :: Lens' CheckDetail (Maybe CheckStatus)
checkDetail_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe CheckStatus
status :: Maybe CheckStatus
$sel:status:CheckDetail' :: CheckDetail -> Maybe CheckStatus
status} -> Maybe CheckStatus
status) (\s :: CheckDetail
s@CheckDetail' {} Maybe CheckStatus
a -> CheckDetail
s {$sel:status:CheckDetail' :: Maybe CheckStatus
status = Maybe CheckStatus
a} :: CheckDetail)

-- | Undocumented member.
checkDetail_updatedAt :: Lens.Lens' CheckDetail (Prelude.Maybe Prelude.UTCTime)
checkDetail_updatedAt :: Lens' CheckDetail (Maybe UTCTime)
checkDetail_updatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CheckDetail' {Maybe POSIX
updatedAt :: Maybe POSIX
$sel:updatedAt:CheckDetail' :: CheckDetail -> Maybe POSIX
updatedAt} -> Maybe POSIX
updatedAt) (\s :: CheckDetail
s@CheckDetail' {} Maybe POSIX
a -> CheckDetail
s {$sel:updatedAt:CheckDetail' :: Maybe POSIX
updatedAt = Maybe POSIX
a} :: CheckDetail) 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

instance Data.FromJSON CheckDetail where
  parseJSON :: Value -> Parser CheckDetail
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"CheckDetail"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe CheckProvider
-> Maybe Text
-> Maybe CheckFailureReason
-> Maybe CheckStatus
-> Maybe POSIX
-> CheckDetail
CheckDetail'
            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
"AccountId")
            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
"ChoiceId")
            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
"Description")
            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
"FlaggedResources")
            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
"Id")
            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
"LensArn")
            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
"Name")
            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
"PillarId")
            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
"Provider")
            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
"QuestionId")
            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
"Reason")
            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
"Status")
            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
"UpdatedAt")
      )

instance Prelude.Hashable CheckDetail where
  hashWithSalt :: Int -> CheckDetail -> Int
hashWithSalt Int
_salt CheckDetail' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe CheckFailureReason
Maybe CheckProvider
Maybe CheckStatus
updatedAt :: Maybe POSIX
status :: Maybe CheckStatus
reason :: Maybe CheckFailureReason
questionId :: Maybe Text
provider :: Maybe CheckProvider
pillarId :: Maybe Text
name :: Maybe Text
lensArn :: Maybe Text
id :: Maybe Text
flaggedResources :: Maybe Natural
description :: Maybe Text
choiceId :: Maybe Text
accountId :: Maybe Text
$sel:updatedAt:CheckDetail' :: CheckDetail -> Maybe POSIX
$sel:status:CheckDetail' :: CheckDetail -> Maybe CheckStatus
$sel:reason:CheckDetail' :: CheckDetail -> Maybe CheckFailureReason
$sel:questionId:CheckDetail' :: CheckDetail -> Maybe Text
$sel:provider:CheckDetail' :: CheckDetail -> Maybe CheckProvider
$sel:pillarId:CheckDetail' :: CheckDetail -> Maybe Text
$sel:name:CheckDetail' :: CheckDetail -> Maybe Text
$sel:lensArn:CheckDetail' :: CheckDetail -> Maybe Text
$sel:id:CheckDetail' :: CheckDetail -> Maybe Text
$sel:flaggedResources:CheckDetail' :: CheckDetail -> Maybe Natural
$sel:description:CheckDetail' :: CheckDetail -> Maybe Text
$sel:choiceId:CheckDetail' :: CheckDetail -> Maybe Text
$sel:accountId:CheckDetail' :: CheckDetail -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
choiceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
flaggedResources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
lensArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pillarId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CheckProvider
provider
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
questionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CheckFailureReason
reason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CheckStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
updatedAt

instance Prelude.NFData CheckDetail where
  rnf :: CheckDetail -> ()
rnf CheckDetail' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe CheckFailureReason
Maybe CheckProvider
Maybe CheckStatus
updatedAt :: Maybe POSIX
status :: Maybe CheckStatus
reason :: Maybe CheckFailureReason
questionId :: Maybe Text
provider :: Maybe CheckProvider
pillarId :: Maybe Text
name :: Maybe Text
lensArn :: Maybe Text
id :: Maybe Text
flaggedResources :: Maybe Natural
description :: Maybe Text
choiceId :: Maybe Text
accountId :: Maybe Text
$sel:updatedAt:CheckDetail' :: CheckDetail -> Maybe POSIX
$sel:status:CheckDetail' :: CheckDetail -> Maybe CheckStatus
$sel:reason:CheckDetail' :: CheckDetail -> Maybe CheckFailureReason
$sel:questionId:CheckDetail' :: CheckDetail -> Maybe Text
$sel:provider:CheckDetail' :: CheckDetail -> Maybe CheckProvider
$sel:pillarId:CheckDetail' :: CheckDetail -> Maybe Text
$sel:name:CheckDetail' :: CheckDetail -> Maybe Text
$sel:lensArn:CheckDetail' :: CheckDetail -> Maybe Text
$sel:id:CheckDetail' :: CheckDetail -> Maybe Text
$sel:flaggedResources:CheckDetail' :: CheckDetail -> Maybe Natural
$sel:description:CheckDetail' :: CheckDetail -> Maybe Text
$sel:choiceId:CheckDetail' :: CheckDetail -> Maybe Text
$sel:accountId:CheckDetail' :: CheckDetail -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
choiceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
flaggedResources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lensArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pillarId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CheckProvider
provider
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
questionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CheckFailureReason
reason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CheckStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
updatedAt