{-# 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.SSM.Types.ComplianceItem
-- 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.SSM.Types.ComplianceItem 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.SSM.Types.ComplianceExecutionSummary
import Amazonka.SSM.Types.ComplianceSeverity
import Amazonka.SSM.Types.ComplianceStatus

-- | Information about the compliance as defined by the resource type. For
-- example, for a patch resource type, @Items@ includes information about
-- the PatchSeverity, Classification, and so on.
--
-- /See:/ 'newComplianceItem' smart constructor.
data ComplianceItem = ComplianceItem'
  { -- | The compliance type. For example, Association (for a State Manager
    -- association), Patch, or Custom:@string@ are all valid compliance types.
    ComplianceItem -> Maybe Text
complianceType :: Prelude.Maybe Prelude.Text,
    -- | A \"Key\": \"Value\" tag combination for the compliance item.
    ComplianceItem -> Maybe (HashMap Text Text)
details :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | A summary for the compliance item. The summary includes an execution ID,
    -- the execution type (for example, command), and the execution time.
    ComplianceItem -> Maybe ComplianceExecutionSummary
executionSummary :: Prelude.Maybe ComplianceExecutionSummary,
    -- | An ID for the compliance item. For example, if the compliance item is a
    -- Windows patch, the ID could be the number of the KB article; for
    -- example: KB4010320.
    ComplianceItem -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | An ID for the resource. For a managed node, this is the node ID.
    ComplianceItem -> Maybe Text
resourceId :: Prelude.Maybe Prelude.Text,
    -- | The type of resource. @ManagedInstance@ is currently the only supported
    -- resource type.
    ComplianceItem -> Maybe Text
resourceType :: Prelude.Maybe Prelude.Text,
    -- | The severity of the compliance status. Severity can be one of the
    -- following: Critical, High, Medium, Low, Informational, Unspecified.
    ComplianceItem -> Maybe ComplianceSeverity
severity :: Prelude.Maybe ComplianceSeverity,
    -- | The status of the compliance item. An item is either COMPLIANT,
    -- NON_COMPLIANT, or an empty string (for Windows patches that aren\'t
    -- applicable).
    ComplianceItem -> Maybe ComplianceStatus
status :: Prelude.Maybe ComplianceStatus,
    -- | A title for the compliance item. For example, if the compliance item is
    -- a Windows patch, the title could be the title of the KB article for the
    -- patch; for example: Security Update for Active Directory Federation
    -- Services.
    ComplianceItem -> Maybe Text
title :: Prelude.Maybe Prelude.Text
  }
  deriving (ComplianceItem -> ComplianceItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ComplianceItem -> ComplianceItem -> Bool
$c/= :: ComplianceItem -> ComplianceItem -> Bool
== :: ComplianceItem -> ComplianceItem -> Bool
$c== :: ComplianceItem -> ComplianceItem -> Bool
Prelude.Eq, ReadPrec [ComplianceItem]
ReadPrec ComplianceItem
Int -> ReadS ComplianceItem
ReadS [ComplianceItem]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ComplianceItem]
$creadListPrec :: ReadPrec [ComplianceItem]
readPrec :: ReadPrec ComplianceItem
$creadPrec :: ReadPrec ComplianceItem
readList :: ReadS [ComplianceItem]
$creadList :: ReadS [ComplianceItem]
readsPrec :: Int -> ReadS ComplianceItem
$creadsPrec :: Int -> ReadS ComplianceItem
Prelude.Read, Int -> ComplianceItem -> ShowS
[ComplianceItem] -> ShowS
ComplianceItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ComplianceItem] -> ShowS
$cshowList :: [ComplianceItem] -> ShowS
show :: ComplianceItem -> String
$cshow :: ComplianceItem -> String
showsPrec :: Int -> ComplianceItem -> ShowS
$cshowsPrec :: Int -> ComplianceItem -> ShowS
Prelude.Show, forall x. Rep ComplianceItem x -> ComplianceItem
forall x. ComplianceItem -> Rep ComplianceItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ComplianceItem x -> ComplianceItem
$cfrom :: forall x. ComplianceItem -> Rep ComplianceItem x
Prelude.Generic)

-- |
-- Create a value of 'ComplianceItem' 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:
--
-- 'complianceType', 'complianceItem_complianceType' - The compliance type. For example, Association (for a State Manager
-- association), Patch, or Custom:@string@ are all valid compliance types.
--
-- 'details', 'complianceItem_details' - A \"Key\": \"Value\" tag combination for the compliance item.
--
-- 'executionSummary', 'complianceItem_executionSummary' - A summary for the compliance item. The summary includes an execution ID,
-- the execution type (for example, command), and the execution time.
--
-- 'id', 'complianceItem_id' - An ID for the compliance item. For example, if the compliance item is a
-- Windows patch, the ID could be the number of the KB article; for
-- example: KB4010320.
--
-- 'resourceId', 'complianceItem_resourceId' - An ID for the resource. For a managed node, this is the node ID.
--
-- 'resourceType', 'complianceItem_resourceType' - The type of resource. @ManagedInstance@ is currently the only supported
-- resource type.
--
-- 'severity', 'complianceItem_severity' - The severity of the compliance status. Severity can be one of the
-- following: Critical, High, Medium, Low, Informational, Unspecified.
--
-- 'status', 'complianceItem_status' - The status of the compliance item. An item is either COMPLIANT,
-- NON_COMPLIANT, or an empty string (for Windows patches that aren\'t
-- applicable).
--
-- 'title', 'complianceItem_title' - A title for the compliance item. For example, if the compliance item is
-- a Windows patch, the title could be the title of the KB article for the
-- patch; for example: Security Update for Active Directory Federation
-- Services.
newComplianceItem ::
  ComplianceItem
newComplianceItem :: ComplianceItem
newComplianceItem =
  ComplianceItem'
    { $sel:complianceType:ComplianceItem' :: Maybe Text
complianceType = forall a. Maybe a
Prelude.Nothing,
      $sel:details:ComplianceItem' :: Maybe (HashMap Text Text)
details = forall a. Maybe a
Prelude.Nothing,
      $sel:executionSummary:ComplianceItem' :: Maybe ComplianceExecutionSummary
executionSummary = forall a. Maybe a
Prelude.Nothing,
      $sel:id:ComplianceItem' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceId:ComplianceItem' :: Maybe Text
resourceId = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceType:ComplianceItem' :: Maybe Text
resourceType = forall a. Maybe a
Prelude.Nothing,
      $sel:severity:ComplianceItem' :: Maybe ComplianceSeverity
severity = forall a. Maybe a
Prelude.Nothing,
      $sel:status:ComplianceItem' :: Maybe ComplianceStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:title:ComplianceItem' :: Maybe Text
title = forall a. Maybe a
Prelude.Nothing
    }

-- | The compliance type. For example, Association (for a State Manager
-- association), Patch, or Custom:@string@ are all valid compliance types.
complianceItem_complianceType :: Lens.Lens' ComplianceItem (Prelude.Maybe Prelude.Text)
complianceItem_complianceType :: Lens' ComplianceItem (Maybe Text)
complianceItem_complianceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ComplianceItem' {Maybe Text
complianceType :: Maybe Text
$sel:complianceType:ComplianceItem' :: ComplianceItem -> Maybe Text
complianceType} -> Maybe Text
complianceType) (\s :: ComplianceItem
s@ComplianceItem' {} Maybe Text
a -> ComplianceItem
s {$sel:complianceType:ComplianceItem' :: Maybe Text
complianceType = Maybe Text
a} :: ComplianceItem)

-- | A \"Key\": \"Value\" tag combination for the compliance item.
complianceItem_details :: Lens.Lens' ComplianceItem (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
complianceItem_details :: Lens' ComplianceItem (Maybe (HashMap Text Text))
complianceItem_details = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ComplianceItem' {Maybe (HashMap Text Text)
details :: Maybe (HashMap Text Text)
$sel:details:ComplianceItem' :: ComplianceItem -> Maybe (HashMap Text Text)
details} -> Maybe (HashMap Text Text)
details) (\s :: ComplianceItem
s@ComplianceItem' {} Maybe (HashMap Text Text)
a -> ComplianceItem
s {$sel:details:ComplianceItem' :: Maybe (HashMap Text Text)
details = Maybe (HashMap Text Text)
a} :: ComplianceItem) 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

-- | A summary for the compliance item. The summary includes an execution ID,
-- the execution type (for example, command), and the execution time.
complianceItem_executionSummary :: Lens.Lens' ComplianceItem (Prelude.Maybe ComplianceExecutionSummary)
complianceItem_executionSummary :: Lens' ComplianceItem (Maybe ComplianceExecutionSummary)
complianceItem_executionSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ComplianceItem' {Maybe ComplianceExecutionSummary
executionSummary :: Maybe ComplianceExecutionSummary
$sel:executionSummary:ComplianceItem' :: ComplianceItem -> Maybe ComplianceExecutionSummary
executionSummary} -> Maybe ComplianceExecutionSummary
executionSummary) (\s :: ComplianceItem
s@ComplianceItem' {} Maybe ComplianceExecutionSummary
a -> ComplianceItem
s {$sel:executionSummary:ComplianceItem' :: Maybe ComplianceExecutionSummary
executionSummary = Maybe ComplianceExecutionSummary
a} :: ComplianceItem)

-- | An ID for the compliance item. For example, if the compliance item is a
-- Windows patch, the ID could be the number of the KB article; for
-- example: KB4010320.
complianceItem_id :: Lens.Lens' ComplianceItem (Prelude.Maybe Prelude.Text)
complianceItem_id :: Lens' ComplianceItem (Maybe Text)
complianceItem_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ComplianceItem' {Maybe Text
id :: Maybe Text
$sel:id:ComplianceItem' :: ComplianceItem -> Maybe Text
id} -> Maybe Text
id) (\s :: ComplianceItem
s@ComplianceItem' {} Maybe Text
a -> ComplianceItem
s {$sel:id:ComplianceItem' :: Maybe Text
id = Maybe Text
a} :: ComplianceItem)

-- | An ID for the resource. For a managed node, this is the node ID.
complianceItem_resourceId :: Lens.Lens' ComplianceItem (Prelude.Maybe Prelude.Text)
complianceItem_resourceId :: Lens' ComplianceItem (Maybe Text)
complianceItem_resourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ComplianceItem' {Maybe Text
resourceId :: Maybe Text
$sel:resourceId:ComplianceItem' :: ComplianceItem -> Maybe Text
resourceId} -> Maybe Text
resourceId) (\s :: ComplianceItem
s@ComplianceItem' {} Maybe Text
a -> ComplianceItem
s {$sel:resourceId:ComplianceItem' :: Maybe Text
resourceId = Maybe Text
a} :: ComplianceItem)

-- | The type of resource. @ManagedInstance@ is currently the only supported
-- resource type.
complianceItem_resourceType :: Lens.Lens' ComplianceItem (Prelude.Maybe Prelude.Text)
complianceItem_resourceType :: Lens' ComplianceItem (Maybe Text)
complianceItem_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ComplianceItem' {Maybe Text
resourceType :: Maybe Text
$sel:resourceType:ComplianceItem' :: ComplianceItem -> Maybe Text
resourceType} -> Maybe Text
resourceType) (\s :: ComplianceItem
s@ComplianceItem' {} Maybe Text
a -> ComplianceItem
s {$sel:resourceType:ComplianceItem' :: Maybe Text
resourceType = Maybe Text
a} :: ComplianceItem)

-- | The severity of the compliance status. Severity can be one of the
-- following: Critical, High, Medium, Low, Informational, Unspecified.
complianceItem_severity :: Lens.Lens' ComplianceItem (Prelude.Maybe ComplianceSeverity)
complianceItem_severity :: Lens' ComplianceItem (Maybe ComplianceSeverity)
complianceItem_severity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ComplianceItem' {Maybe ComplianceSeverity
severity :: Maybe ComplianceSeverity
$sel:severity:ComplianceItem' :: ComplianceItem -> Maybe ComplianceSeverity
severity} -> Maybe ComplianceSeverity
severity) (\s :: ComplianceItem
s@ComplianceItem' {} Maybe ComplianceSeverity
a -> ComplianceItem
s {$sel:severity:ComplianceItem' :: Maybe ComplianceSeverity
severity = Maybe ComplianceSeverity
a} :: ComplianceItem)

-- | The status of the compliance item. An item is either COMPLIANT,
-- NON_COMPLIANT, or an empty string (for Windows patches that aren\'t
-- applicable).
complianceItem_status :: Lens.Lens' ComplianceItem (Prelude.Maybe ComplianceStatus)
complianceItem_status :: Lens' ComplianceItem (Maybe ComplianceStatus)
complianceItem_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ComplianceItem' {Maybe ComplianceStatus
status :: Maybe ComplianceStatus
$sel:status:ComplianceItem' :: ComplianceItem -> Maybe ComplianceStatus
status} -> Maybe ComplianceStatus
status) (\s :: ComplianceItem
s@ComplianceItem' {} Maybe ComplianceStatus
a -> ComplianceItem
s {$sel:status:ComplianceItem' :: Maybe ComplianceStatus
status = Maybe ComplianceStatus
a} :: ComplianceItem)

-- | A title for the compliance item. For example, if the compliance item is
-- a Windows patch, the title could be the title of the KB article for the
-- patch; for example: Security Update for Active Directory Federation
-- Services.
complianceItem_title :: Lens.Lens' ComplianceItem (Prelude.Maybe Prelude.Text)
complianceItem_title :: Lens' ComplianceItem (Maybe Text)
complianceItem_title = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ComplianceItem' {Maybe Text
title :: Maybe Text
$sel:title:ComplianceItem' :: ComplianceItem -> Maybe Text
title} -> Maybe Text
title) (\s :: ComplianceItem
s@ComplianceItem' {} Maybe Text
a -> ComplianceItem
s {$sel:title:ComplianceItem' :: Maybe Text
title = Maybe Text
a} :: ComplianceItem)

instance Data.FromJSON ComplianceItem where
  parseJSON :: Value -> Parser ComplianceItem
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ComplianceItem"
      ( \Object
x ->
          Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe ComplianceExecutionSummary
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ComplianceSeverity
-> Maybe ComplianceStatus
-> Maybe Text
-> ComplianceItem
ComplianceItem'
            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
"ComplianceType")
            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
"Details" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"ExecutionSummary")
            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
"ResourceId")
            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
"ResourceType")
            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
"Severity")
            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
"Title")
      )

instance Prelude.Hashable ComplianceItem where
  hashWithSalt :: Int -> ComplianceItem -> Int
hashWithSalt Int
_salt ComplianceItem' {Maybe Text
Maybe (HashMap Text Text)
Maybe ComplianceExecutionSummary
Maybe ComplianceSeverity
Maybe ComplianceStatus
title :: Maybe Text
status :: Maybe ComplianceStatus
severity :: Maybe ComplianceSeverity
resourceType :: Maybe Text
resourceId :: Maybe Text
id :: Maybe Text
executionSummary :: Maybe ComplianceExecutionSummary
details :: Maybe (HashMap Text Text)
complianceType :: Maybe Text
$sel:title:ComplianceItem' :: ComplianceItem -> Maybe Text
$sel:status:ComplianceItem' :: ComplianceItem -> Maybe ComplianceStatus
$sel:severity:ComplianceItem' :: ComplianceItem -> Maybe ComplianceSeverity
$sel:resourceType:ComplianceItem' :: ComplianceItem -> Maybe Text
$sel:resourceId:ComplianceItem' :: ComplianceItem -> Maybe Text
$sel:id:ComplianceItem' :: ComplianceItem -> Maybe Text
$sel:executionSummary:ComplianceItem' :: ComplianceItem -> Maybe ComplianceExecutionSummary
$sel:details:ComplianceItem' :: ComplianceItem -> Maybe (HashMap Text Text)
$sel:complianceType:ComplianceItem' :: ComplianceItem -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
complianceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
details
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComplianceExecutionSummary
executionSummary
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComplianceSeverity
severity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComplianceStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
title

instance Prelude.NFData ComplianceItem where
  rnf :: ComplianceItem -> ()
rnf ComplianceItem' {Maybe Text
Maybe (HashMap Text Text)
Maybe ComplianceExecutionSummary
Maybe ComplianceSeverity
Maybe ComplianceStatus
title :: Maybe Text
status :: Maybe ComplianceStatus
severity :: Maybe ComplianceSeverity
resourceType :: Maybe Text
resourceId :: Maybe Text
id :: Maybe Text
executionSummary :: Maybe ComplianceExecutionSummary
details :: Maybe (HashMap Text Text)
complianceType :: Maybe Text
$sel:title:ComplianceItem' :: ComplianceItem -> Maybe Text
$sel:status:ComplianceItem' :: ComplianceItem -> Maybe ComplianceStatus
$sel:severity:ComplianceItem' :: ComplianceItem -> Maybe ComplianceSeverity
$sel:resourceType:ComplianceItem' :: ComplianceItem -> Maybe Text
$sel:resourceId:ComplianceItem' :: ComplianceItem -> Maybe Text
$sel:id:ComplianceItem' :: ComplianceItem -> Maybe Text
$sel:executionSummary:ComplianceItem' :: ComplianceItem -> Maybe ComplianceExecutionSummary
$sel:details:ComplianceItem' :: ComplianceItem -> Maybe (HashMap Text Text)
$sel:complianceType:ComplianceItem' :: ComplianceItem -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
complianceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
details
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComplianceExecutionSummary
executionSummary
      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
resourceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComplianceSeverity
severity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComplianceStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
title