{-# 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.AccessAnalyzer.Types.AnalyzerSummary
-- 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.AccessAnalyzer.Types.AnalyzerSummary where

import Amazonka.AccessAnalyzer.Types.AnalyzerStatus
import Amazonka.AccessAnalyzer.Types.StatusReason
import Amazonka.AccessAnalyzer.Types.Type
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

-- | Contains information about the analyzer.
--
-- /See:/ 'newAnalyzerSummary' smart constructor.
data AnalyzerSummary = AnalyzerSummary'
  { -- | The resource that was most recently analyzed by the analyzer.
    AnalyzerSummary -> Maybe Text
lastResourceAnalyzed :: Prelude.Maybe Prelude.Text,
    -- | The time at which the most recently analyzed resource was analyzed.
    AnalyzerSummary -> Maybe ISO8601
lastResourceAnalyzedAt :: Prelude.Maybe Data.ISO8601,
    -- | The @statusReason@ provides more details about the current status of the
    -- analyzer. For example, if the creation for the analyzer fails, a
    -- @Failed@ status is returned. For an analyzer with organization as the
    -- type, this failure can be due to an issue with creating the
    -- service-linked roles required in the member accounts of the Amazon Web
    -- Services organization.
    AnalyzerSummary -> Maybe StatusReason
statusReason :: Prelude.Maybe StatusReason,
    -- | The tags added to the analyzer.
    AnalyzerSummary -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The ARN of the analyzer.
    AnalyzerSummary -> Text
arn :: Prelude.Text,
    -- | The name of the analyzer.
    AnalyzerSummary -> Text
name :: Prelude.Text,
    -- | The type of analyzer, which corresponds to the zone of trust chosen for
    -- the analyzer.
    AnalyzerSummary -> Type
type' :: Type,
    -- | A timestamp for the time at which the analyzer was created.
    AnalyzerSummary -> ISO8601
createdAt :: Data.ISO8601,
    -- | The status of the analyzer. An @Active@ analyzer successfully monitors
    -- supported resources and generates new findings. The analyzer is
    -- @Disabled@ when a user action, such as removing trusted access for
    -- Identity and Access Management Access Analyzer from Organizations,
    -- causes the analyzer to stop generating new findings. The status is
    -- @Creating@ when the analyzer creation is in progress and @Failed@ when
    -- the analyzer creation has failed.
    AnalyzerSummary -> AnalyzerStatus
status :: AnalyzerStatus
  }
  deriving (AnalyzerSummary -> AnalyzerSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnalyzerSummary -> AnalyzerSummary -> Bool
$c/= :: AnalyzerSummary -> AnalyzerSummary -> Bool
== :: AnalyzerSummary -> AnalyzerSummary -> Bool
$c== :: AnalyzerSummary -> AnalyzerSummary -> Bool
Prelude.Eq, ReadPrec [AnalyzerSummary]
ReadPrec AnalyzerSummary
Int -> ReadS AnalyzerSummary
ReadS [AnalyzerSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AnalyzerSummary]
$creadListPrec :: ReadPrec [AnalyzerSummary]
readPrec :: ReadPrec AnalyzerSummary
$creadPrec :: ReadPrec AnalyzerSummary
readList :: ReadS [AnalyzerSummary]
$creadList :: ReadS [AnalyzerSummary]
readsPrec :: Int -> ReadS AnalyzerSummary
$creadsPrec :: Int -> ReadS AnalyzerSummary
Prelude.Read, Int -> AnalyzerSummary -> ShowS
[AnalyzerSummary] -> ShowS
AnalyzerSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnalyzerSummary] -> ShowS
$cshowList :: [AnalyzerSummary] -> ShowS
show :: AnalyzerSummary -> String
$cshow :: AnalyzerSummary -> String
showsPrec :: Int -> AnalyzerSummary -> ShowS
$cshowsPrec :: Int -> AnalyzerSummary -> ShowS
Prelude.Show, forall x. Rep AnalyzerSummary x -> AnalyzerSummary
forall x. AnalyzerSummary -> Rep AnalyzerSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnalyzerSummary x -> AnalyzerSummary
$cfrom :: forall x. AnalyzerSummary -> Rep AnalyzerSummary x
Prelude.Generic)

-- |
-- Create a value of 'AnalyzerSummary' 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:
--
-- 'lastResourceAnalyzed', 'analyzerSummary_lastResourceAnalyzed' - The resource that was most recently analyzed by the analyzer.
--
-- 'lastResourceAnalyzedAt', 'analyzerSummary_lastResourceAnalyzedAt' - The time at which the most recently analyzed resource was analyzed.
--
-- 'statusReason', 'analyzerSummary_statusReason' - The @statusReason@ provides more details about the current status of the
-- analyzer. For example, if the creation for the analyzer fails, a
-- @Failed@ status is returned. For an analyzer with organization as the
-- type, this failure can be due to an issue with creating the
-- service-linked roles required in the member accounts of the Amazon Web
-- Services organization.
--
-- 'tags', 'analyzerSummary_tags' - The tags added to the analyzer.
--
-- 'arn', 'analyzerSummary_arn' - The ARN of the analyzer.
--
-- 'name', 'analyzerSummary_name' - The name of the analyzer.
--
-- 'type'', 'analyzerSummary_type' - The type of analyzer, which corresponds to the zone of trust chosen for
-- the analyzer.
--
-- 'createdAt', 'analyzerSummary_createdAt' - A timestamp for the time at which the analyzer was created.
--
-- 'status', 'analyzerSummary_status' - The status of the analyzer. An @Active@ analyzer successfully monitors
-- supported resources and generates new findings. The analyzer is
-- @Disabled@ when a user action, such as removing trusted access for
-- Identity and Access Management Access Analyzer from Organizations,
-- causes the analyzer to stop generating new findings. The status is
-- @Creating@ when the analyzer creation is in progress and @Failed@ when
-- the analyzer creation has failed.
newAnalyzerSummary ::
  -- | 'arn'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  -- | 'type''
  Type ->
  -- | 'createdAt'
  Prelude.UTCTime ->
  -- | 'status'
  AnalyzerStatus ->
  AnalyzerSummary
newAnalyzerSummary :: Text
-> Text -> Type -> UTCTime -> AnalyzerStatus -> AnalyzerSummary
newAnalyzerSummary
  Text
pArn_
  Text
pName_
  Type
pType_
  UTCTime
pCreatedAt_
  AnalyzerStatus
pStatus_ =
    AnalyzerSummary'
      { $sel:lastResourceAnalyzed:AnalyzerSummary' :: Maybe Text
lastResourceAnalyzed =
          forall a. Maybe a
Prelude.Nothing,
        $sel:lastResourceAnalyzedAt:AnalyzerSummary' :: Maybe ISO8601
lastResourceAnalyzedAt = forall a. Maybe a
Prelude.Nothing,
        $sel:statusReason:AnalyzerSummary' :: Maybe StatusReason
statusReason = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:AnalyzerSummary' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:arn:AnalyzerSummary' :: Text
arn = Text
pArn_,
        $sel:name:AnalyzerSummary' :: Text
name = Text
pName_,
        $sel:type':AnalyzerSummary' :: Type
type' = Type
pType_,
        $sel:createdAt:AnalyzerSummary' :: ISO8601
createdAt = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreatedAt_,
        $sel:status:AnalyzerSummary' :: AnalyzerStatus
status = AnalyzerStatus
pStatus_
      }

-- | The resource that was most recently analyzed by the analyzer.
analyzerSummary_lastResourceAnalyzed :: Lens.Lens' AnalyzerSummary (Prelude.Maybe Prelude.Text)
analyzerSummary_lastResourceAnalyzed :: Lens' AnalyzerSummary (Maybe Text)
analyzerSummary_lastResourceAnalyzed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnalyzerSummary' {Maybe Text
lastResourceAnalyzed :: Maybe Text
$sel:lastResourceAnalyzed:AnalyzerSummary' :: AnalyzerSummary -> Maybe Text
lastResourceAnalyzed} -> Maybe Text
lastResourceAnalyzed) (\s :: AnalyzerSummary
s@AnalyzerSummary' {} Maybe Text
a -> AnalyzerSummary
s {$sel:lastResourceAnalyzed:AnalyzerSummary' :: Maybe Text
lastResourceAnalyzed = Maybe Text
a} :: AnalyzerSummary)

-- | The time at which the most recently analyzed resource was analyzed.
analyzerSummary_lastResourceAnalyzedAt :: Lens.Lens' AnalyzerSummary (Prelude.Maybe Prelude.UTCTime)
analyzerSummary_lastResourceAnalyzedAt :: Lens' AnalyzerSummary (Maybe UTCTime)
analyzerSummary_lastResourceAnalyzedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnalyzerSummary' {Maybe ISO8601
lastResourceAnalyzedAt :: Maybe ISO8601
$sel:lastResourceAnalyzedAt:AnalyzerSummary' :: AnalyzerSummary -> Maybe ISO8601
lastResourceAnalyzedAt} -> Maybe ISO8601
lastResourceAnalyzedAt) (\s :: AnalyzerSummary
s@AnalyzerSummary' {} Maybe ISO8601
a -> AnalyzerSummary
s {$sel:lastResourceAnalyzedAt:AnalyzerSummary' :: Maybe ISO8601
lastResourceAnalyzedAt = Maybe ISO8601
a} :: AnalyzerSummary) 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 @statusReason@ provides more details about the current status of the
-- analyzer. For example, if the creation for the analyzer fails, a
-- @Failed@ status is returned. For an analyzer with organization as the
-- type, this failure can be due to an issue with creating the
-- service-linked roles required in the member accounts of the Amazon Web
-- Services organization.
analyzerSummary_statusReason :: Lens.Lens' AnalyzerSummary (Prelude.Maybe StatusReason)
analyzerSummary_statusReason :: Lens' AnalyzerSummary (Maybe StatusReason)
analyzerSummary_statusReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnalyzerSummary' {Maybe StatusReason
statusReason :: Maybe StatusReason
$sel:statusReason:AnalyzerSummary' :: AnalyzerSummary -> Maybe StatusReason
statusReason} -> Maybe StatusReason
statusReason) (\s :: AnalyzerSummary
s@AnalyzerSummary' {} Maybe StatusReason
a -> AnalyzerSummary
s {$sel:statusReason:AnalyzerSummary' :: Maybe StatusReason
statusReason = Maybe StatusReason
a} :: AnalyzerSummary)

-- | The tags added to the analyzer.
analyzerSummary_tags :: Lens.Lens' AnalyzerSummary (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
analyzerSummary_tags :: Lens' AnalyzerSummary (Maybe (HashMap Text Text))
analyzerSummary_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnalyzerSummary' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:AnalyzerSummary' :: AnalyzerSummary -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: AnalyzerSummary
s@AnalyzerSummary' {} Maybe (HashMap Text Text)
a -> AnalyzerSummary
s {$sel:tags:AnalyzerSummary' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: AnalyzerSummary) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The ARN of the analyzer.
analyzerSummary_arn :: Lens.Lens' AnalyzerSummary Prelude.Text
analyzerSummary_arn :: Lens' AnalyzerSummary Text
analyzerSummary_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnalyzerSummary' {Text
arn :: Text
$sel:arn:AnalyzerSummary' :: AnalyzerSummary -> Text
arn} -> Text
arn) (\s :: AnalyzerSummary
s@AnalyzerSummary' {} Text
a -> AnalyzerSummary
s {$sel:arn:AnalyzerSummary' :: Text
arn = Text
a} :: AnalyzerSummary)

-- | The name of the analyzer.
analyzerSummary_name :: Lens.Lens' AnalyzerSummary Prelude.Text
analyzerSummary_name :: Lens' AnalyzerSummary Text
analyzerSummary_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnalyzerSummary' {Text
name :: Text
$sel:name:AnalyzerSummary' :: AnalyzerSummary -> Text
name} -> Text
name) (\s :: AnalyzerSummary
s@AnalyzerSummary' {} Text
a -> AnalyzerSummary
s {$sel:name:AnalyzerSummary' :: Text
name = Text
a} :: AnalyzerSummary)

-- | The type of analyzer, which corresponds to the zone of trust chosen for
-- the analyzer.
analyzerSummary_type :: Lens.Lens' AnalyzerSummary Type
analyzerSummary_type :: Lens' AnalyzerSummary Type
analyzerSummary_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnalyzerSummary' {Type
type' :: Type
$sel:type':AnalyzerSummary' :: AnalyzerSummary -> Type
type'} -> Type
type') (\s :: AnalyzerSummary
s@AnalyzerSummary' {} Type
a -> AnalyzerSummary
s {$sel:type':AnalyzerSummary' :: Type
type' = Type
a} :: AnalyzerSummary)

-- | A timestamp for the time at which the analyzer was created.
analyzerSummary_createdAt :: Lens.Lens' AnalyzerSummary Prelude.UTCTime
analyzerSummary_createdAt :: Lens' AnalyzerSummary UTCTime
analyzerSummary_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnalyzerSummary' {ISO8601
createdAt :: ISO8601
$sel:createdAt:AnalyzerSummary' :: AnalyzerSummary -> ISO8601
createdAt} -> ISO8601
createdAt) (\s :: AnalyzerSummary
s@AnalyzerSummary' {} ISO8601
a -> AnalyzerSummary
s {$sel:createdAt:AnalyzerSummary' :: ISO8601
createdAt = ISO8601
a} :: AnalyzerSummary) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The status of the analyzer. An @Active@ analyzer successfully monitors
-- supported resources and generates new findings. The analyzer is
-- @Disabled@ when a user action, such as removing trusted access for
-- Identity and Access Management Access Analyzer from Organizations,
-- causes the analyzer to stop generating new findings. The status is
-- @Creating@ when the analyzer creation is in progress and @Failed@ when
-- the analyzer creation has failed.
analyzerSummary_status :: Lens.Lens' AnalyzerSummary AnalyzerStatus
analyzerSummary_status :: Lens' AnalyzerSummary AnalyzerStatus
analyzerSummary_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnalyzerSummary' {AnalyzerStatus
status :: AnalyzerStatus
$sel:status:AnalyzerSummary' :: AnalyzerSummary -> AnalyzerStatus
status} -> AnalyzerStatus
status) (\s :: AnalyzerSummary
s@AnalyzerSummary' {} AnalyzerStatus
a -> AnalyzerSummary
s {$sel:status:AnalyzerSummary' :: AnalyzerStatus
status = AnalyzerStatus
a} :: AnalyzerSummary)

instance Data.FromJSON AnalyzerSummary where
  parseJSON :: Value -> Parser AnalyzerSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AnalyzerSummary"
      ( \Object
x ->
          Maybe Text
-> Maybe ISO8601
-> Maybe StatusReason
-> Maybe (HashMap Text Text)
-> Text
-> Text
-> Type
-> ISO8601
-> AnalyzerStatus
-> AnalyzerSummary
AnalyzerSummary'
            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
"lastResourceAnalyzed")
            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
"lastResourceAnalyzedAt")
            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
"statusReason")
            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
"tags" 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 a
Data..: Key
"arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser 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 a
Data..: Key
"type")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"createdAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"status")
      )

instance Prelude.Hashable AnalyzerSummary where
  hashWithSalt :: Int -> AnalyzerSummary -> Int
hashWithSalt Int
_salt AnalyzerSummary' {Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
Maybe StatusReason
Text
ISO8601
AnalyzerStatus
Type
status :: AnalyzerStatus
createdAt :: ISO8601
type' :: Type
name :: Text
arn :: Text
tags :: Maybe (HashMap Text Text)
statusReason :: Maybe StatusReason
lastResourceAnalyzedAt :: Maybe ISO8601
lastResourceAnalyzed :: Maybe Text
$sel:status:AnalyzerSummary' :: AnalyzerSummary -> AnalyzerStatus
$sel:createdAt:AnalyzerSummary' :: AnalyzerSummary -> ISO8601
$sel:type':AnalyzerSummary' :: AnalyzerSummary -> Type
$sel:name:AnalyzerSummary' :: AnalyzerSummary -> Text
$sel:arn:AnalyzerSummary' :: AnalyzerSummary -> Text
$sel:tags:AnalyzerSummary' :: AnalyzerSummary -> Maybe (HashMap Text Text)
$sel:statusReason:AnalyzerSummary' :: AnalyzerSummary -> Maybe StatusReason
$sel:lastResourceAnalyzedAt:AnalyzerSummary' :: AnalyzerSummary -> Maybe ISO8601
$sel:lastResourceAnalyzed:AnalyzerSummary' :: AnalyzerSummary -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
lastResourceAnalyzed
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
lastResourceAnalyzedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StatusReason
statusReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Type
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ISO8601
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AnalyzerStatus
status

instance Prelude.NFData AnalyzerSummary where
  rnf :: AnalyzerSummary -> ()
rnf AnalyzerSummary' {Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
Maybe StatusReason
Text
ISO8601
AnalyzerStatus
Type
status :: AnalyzerStatus
createdAt :: ISO8601
type' :: Type
name :: Text
arn :: Text
tags :: Maybe (HashMap Text Text)
statusReason :: Maybe StatusReason
lastResourceAnalyzedAt :: Maybe ISO8601
lastResourceAnalyzed :: Maybe Text
$sel:status:AnalyzerSummary' :: AnalyzerSummary -> AnalyzerStatus
$sel:createdAt:AnalyzerSummary' :: AnalyzerSummary -> ISO8601
$sel:type':AnalyzerSummary' :: AnalyzerSummary -> Type
$sel:name:AnalyzerSummary' :: AnalyzerSummary -> Text
$sel:arn:AnalyzerSummary' :: AnalyzerSummary -> Text
$sel:tags:AnalyzerSummary' :: AnalyzerSummary -> Maybe (HashMap Text Text)
$sel:statusReason:AnalyzerSummary' :: AnalyzerSummary -> Maybe StatusReason
$sel:lastResourceAnalyzedAt:AnalyzerSummary' :: AnalyzerSummary -> Maybe ISO8601
$sel:lastResourceAnalyzed:AnalyzerSummary' :: AnalyzerSummary -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastResourceAnalyzed
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
lastResourceAnalyzedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StatusReason
statusReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Type
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ISO8601
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AnalyzerStatus
status