{-# 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.Config.Types.AggregateEvaluationResult
-- 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.Config.Types.AggregateEvaluationResult where

import Amazonka.Config.Types.ComplianceType
import Amazonka.Config.Types.EvaluationResultIdentifier
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 details of an Config evaluation for an account ID and region in an
-- aggregator. Provides the Amazon Web Services resource that was
-- evaluated, the compliance of the resource, related time stamps, and
-- supplementary information.
--
-- /See:/ 'newAggregateEvaluationResult' smart constructor.
data AggregateEvaluationResult = AggregateEvaluationResult'
  { -- | The 12-digit account ID of the source account.
    AggregateEvaluationResult -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text,
    -- | Supplementary information about how the agrregate evaluation determined
    -- the compliance.
    AggregateEvaluationResult -> Maybe Text
annotation :: Prelude.Maybe Prelude.Text,
    -- | The source region from where the data is aggregated.
    AggregateEvaluationResult -> Maybe Text
awsRegion :: Prelude.Maybe Prelude.Text,
    -- | The resource compliance status.
    --
    -- For the @AggregationEvaluationResult@ data type, Config supports only
    -- the @COMPLIANT@ and @NON_COMPLIANT@. Config does not support the
    -- @NOT_APPLICABLE@ and @INSUFFICIENT_DATA@ value.
    AggregateEvaluationResult -> Maybe ComplianceType
complianceType :: Prelude.Maybe ComplianceType,
    -- | The time when the Config rule evaluated the Amazon Web Services
    -- resource.
    AggregateEvaluationResult -> Maybe POSIX
configRuleInvokedTime :: Prelude.Maybe Data.POSIX,
    -- | Uniquely identifies the evaluation result.
    AggregateEvaluationResult -> Maybe EvaluationResultIdentifier
evaluationResultIdentifier :: Prelude.Maybe EvaluationResultIdentifier,
    -- | The time when Config recorded the aggregate evaluation result.
    AggregateEvaluationResult -> Maybe POSIX
resultRecordedTime :: Prelude.Maybe Data.POSIX
  }
  deriving (AggregateEvaluationResult -> AggregateEvaluationResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AggregateEvaluationResult -> AggregateEvaluationResult -> Bool
$c/= :: AggregateEvaluationResult -> AggregateEvaluationResult -> Bool
== :: AggregateEvaluationResult -> AggregateEvaluationResult -> Bool
$c== :: AggregateEvaluationResult -> AggregateEvaluationResult -> Bool
Prelude.Eq, ReadPrec [AggregateEvaluationResult]
ReadPrec AggregateEvaluationResult
Int -> ReadS AggregateEvaluationResult
ReadS [AggregateEvaluationResult]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AggregateEvaluationResult]
$creadListPrec :: ReadPrec [AggregateEvaluationResult]
readPrec :: ReadPrec AggregateEvaluationResult
$creadPrec :: ReadPrec AggregateEvaluationResult
readList :: ReadS [AggregateEvaluationResult]
$creadList :: ReadS [AggregateEvaluationResult]
readsPrec :: Int -> ReadS AggregateEvaluationResult
$creadsPrec :: Int -> ReadS AggregateEvaluationResult
Prelude.Read, Int -> AggregateEvaluationResult -> ShowS
[AggregateEvaluationResult] -> ShowS
AggregateEvaluationResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AggregateEvaluationResult] -> ShowS
$cshowList :: [AggregateEvaluationResult] -> ShowS
show :: AggregateEvaluationResult -> String
$cshow :: AggregateEvaluationResult -> String
showsPrec :: Int -> AggregateEvaluationResult -> ShowS
$cshowsPrec :: Int -> AggregateEvaluationResult -> ShowS
Prelude.Show, forall x.
Rep AggregateEvaluationResult x -> AggregateEvaluationResult
forall x.
AggregateEvaluationResult -> Rep AggregateEvaluationResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AggregateEvaluationResult x -> AggregateEvaluationResult
$cfrom :: forall x.
AggregateEvaluationResult -> Rep AggregateEvaluationResult x
Prelude.Generic)

-- |
-- Create a value of 'AggregateEvaluationResult' 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', 'aggregateEvaluationResult_accountId' - The 12-digit account ID of the source account.
--
-- 'annotation', 'aggregateEvaluationResult_annotation' - Supplementary information about how the agrregate evaluation determined
-- the compliance.
--
-- 'awsRegion', 'aggregateEvaluationResult_awsRegion' - The source region from where the data is aggregated.
--
-- 'complianceType', 'aggregateEvaluationResult_complianceType' - The resource compliance status.
--
-- For the @AggregationEvaluationResult@ data type, Config supports only
-- the @COMPLIANT@ and @NON_COMPLIANT@. Config does not support the
-- @NOT_APPLICABLE@ and @INSUFFICIENT_DATA@ value.
--
-- 'configRuleInvokedTime', 'aggregateEvaluationResult_configRuleInvokedTime' - The time when the Config rule evaluated the Amazon Web Services
-- resource.
--
-- 'evaluationResultIdentifier', 'aggregateEvaluationResult_evaluationResultIdentifier' - Uniquely identifies the evaluation result.
--
-- 'resultRecordedTime', 'aggregateEvaluationResult_resultRecordedTime' - The time when Config recorded the aggregate evaluation result.
newAggregateEvaluationResult ::
  AggregateEvaluationResult
newAggregateEvaluationResult :: AggregateEvaluationResult
newAggregateEvaluationResult =
  AggregateEvaluationResult'
    { $sel:accountId:AggregateEvaluationResult' :: Maybe Text
accountId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:annotation:AggregateEvaluationResult' :: Maybe Text
annotation = forall a. Maybe a
Prelude.Nothing,
      $sel:awsRegion:AggregateEvaluationResult' :: Maybe Text
awsRegion = forall a. Maybe a
Prelude.Nothing,
      $sel:complianceType:AggregateEvaluationResult' :: Maybe ComplianceType
complianceType = forall a. Maybe a
Prelude.Nothing,
      $sel:configRuleInvokedTime:AggregateEvaluationResult' :: Maybe POSIX
configRuleInvokedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:evaluationResultIdentifier:AggregateEvaluationResult' :: Maybe EvaluationResultIdentifier
evaluationResultIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:resultRecordedTime:AggregateEvaluationResult' :: Maybe POSIX
resultRecordedTime = forall a. Maybe a
Prelude.Nothing
    }

-- | The 12-digit account ID of the source account.
aggregateEvaluationResult_accountId :: Lens.Lens' AggregateEvaluationResult (Prelude.Maybe Prelude.Text)
aggregateEvaluationResult_accountId :: Lens' AggregateEvaluationResult (Maybe Text)
aggregateEvaluationResult_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AggregateEvaluationResult' {Maybe Text
accountId :: Maybe Text
$sel:accountId:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe Text
accountId} -> Maybe Text
accountId) (\s :: AggregateEvaluationResult
s@AggregateEvaluationResult' {} Maybe Text
a -> AggregateEvaluationResult
s {$sel:accountId:AggregateEvaluationResult' :: Maybe Text
accountId = Maybe Text
a} :: AggregateEvaluationResult)

-- | Supplementary information about how the agrregate evaluation determined
-- the compliance.
aggregateEvaluationResult_annotation :: Lens.Lens' AggregateEvaluationResult (Prelude.Maybe Prelude.Text)
aggregateEvaluationResult_annotation :: Lens' AggregateEvaluationResult (Maybe Text)
aggregateEvaluationResult_annotation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AggregateEvaluationResult' {Maybe Text
annotation :: Maybe Text
$sel:annotation:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe Text
annotation} -> Maybe Text
annotation) (\s :: AggregateEvaluationResult
s@AggregateEvaluationResult' {} Maybe Text
a -> AggregateEvaluationResult
s {$sel:annotation:AggregateEvaluationResult' :: Maybe Text
annotation = Maybe Text
a} :: AggregateEvaluationResult)

-- | The source region from where the data is aggregated.
aggregateEvaluationResult_awsRegion :: Lens.Lens' AggregateEvaluationResult (Prelude.Maybe Prelude.Text)
aggregateEvaluationResult_awsRegion :: Lens' AggregateEvaluationResult (Maybe Text)
aggregateEvaluationResult_awsRegion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AggregateEvaluationResult' {Maybe Text
awsRegion :: Maybe Text
$sel:awsRegion:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe Text
awsRegion} -> Maybe Text
awsRegion) (\s :: AggregateEvaluationResult
s@AggregateEvaluationResult' {} Maybe Text
a -> AggregateEvaluationResult
s {$sel:awsRegion:AggregateEvaluationResult' :: Maybe Text
awsRegion = Maybe Text
a} :: AggregateEvaluationResult)

-- | The resource compliance status.
--
-- For the @AggregationEvaluationResult@ data type, Config supports only
-- the @COMPLIANT@ and @NON_COMPLIANT@. Config does not support the
-- @NOT_APPLICABLE@ and @INSUFFICIENT_DATA@ value.
aggregateEvaluationResult_complianceType :: Lens.Lens' AggregateEvaluationResult (Prelude.Maybe ComplianceType)
aggregateEvaluationResult_complianceType :: Lens' AggregateEvaluationResult (Maybe ComplianceType)
aggregateEvaluationResult_complianceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AggregateEvaluationResult' {Maybe ComplianceType
complianceType :: Maybe ComplianceType
$sel:complianceType:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe ComplianceType
complianceType} -> Maybe ComplianceType
complianceType) (\s :: AggregateEvaluationResult
s@AggregateEvaluationResult' {} Maybe ComplianceType
a -> AggregateEvaluationResult
s {$sel:complianceType:AggregateEvaluationResult' :: Maybe ComplianceType
complianceType = Maybe ComplianceType
a} :: AggregateEvaluationResult)

-- | The time when the Config rule evaluated the Amazon Web Services
-- resource.
aggregateEvaluationResult_configRuleInvokedTime :: Lens.Lens' AggregateEvaluationResult (Prelude.Maybe Prelude.UTCTime)
aggregateEvaluationResult_configRuleInvokedTime :: Lens' AggregateEvaluationResult (Maybe UTCTime)
aggregateEvaluationResult_configRuleInvokedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AggregateEvaluationResult' {Maybe POSIX
configRuleInvokedTime :: Maybe POSIX
$sel:configRuleInvokedTime:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe POSIX
configRuleInvokedTime} -> Maybe POSIX
configRuleInvokedTime) (\s :: AggregateEvaluationResult
s@AggregateEvaluationResult' {} Maybe POSIX
a -> AggregateEvaluationResult
s {$sel:configRuleInvokedTime:AggregateEvaluationResult' :: Maybe POSIX
configRuleInvokedTime = Maybe POSIX
a} :: AggregateEvaluationResult) 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

-- | Uniquely identifies the evaluation result.
aggregateEvaluationResult_evaluationResultIdentifier :: Lens.Lens' AggregateEvaluationResult (Prelude.Maybe EvaluationResultIdentifier)
aggregateEvaluationResult_evaluationResultIdentifier :: Lens' AggregateEvaluationResult (Maybe EvaluationResultIdentifier)
aggregateEvaluationResult_evaluationResultIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AggregateEvaluationResult' {Maybe EvaluationResultIdentifier
evaluationResultIdentifier :: Maybe EvaluationResultIdentifier
$sel:evaluationResultIdentifier:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe EvaluationResultIdentifier
evaluationResultIdentifier} -> Maybe EvaluationResultIdentifier
evaluationResultIdentifier) (\s :: AggregateEvaluationResult
s@AggregateEvaluationResult' {} Maybe EvaluationResultIdentifier
a -> AggregateEvaluationResult
s {$sel:evaluationResultIdentifier:AggregateEvaluationResult' :: Maybe EvaluationResultIdentifier
evaluationResultIdentifier = Maybe EvaluationResultIdentifier
a} :: AggregateEvaluationResult)

-- | The time when Config recorded the aggregate evaluation result.
aggregateEvaluationResult_resultRecordedTime :: Lens.Lens' AggregateEvaluationResult (Prelude.Maybe Prelude.UTCTime)
aggregateEvaluationResult_resultRecordedTime :: Lens' AggregateEvaluationResult (Maybe UTCTime)
aggregateEvaluationResult_resultRecordedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AggregateEvaluationResult' {Maybe POSIX
resultRecordedTime :: Maybe POSIX
$sel:resultRecordedTime:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe POSIX
resultRecordedTime} -> Maybe POSIX
resultRecordedTime) (\s :: AggregateEvaluationResult
s@AggregateEvaluationResult' {} Maybe POSIX
a -> AggregateEvaluationResult
s {$sel:resultRecordedTime:AggregateEvaluationResult' :: Maybe POSIX
resultRecordedTime = Maybe POSIX
a} :: AggregateEvaluationResult) 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 AggregateEvaluationResult where
  parseJSON :: Value -> Parser AggregateEvaluationResult
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AggregateEvaluationResult"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ComplianceType
-> Maybe POSIX
-> Maybe EvaluationResultIdentifier
-> Maybe POSIX
-> AggregateEvaluationResult
AggregateEvaluationResult'
            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
"Annotation")
            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
"AwsRegion")
            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
"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
"ConfigRuleInvokedTime")
            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
"EvaluationResultIdentifier")
            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
"ResultRecordedTime")
      )

instance Prelude.Hashable AggregateEvaluationResult where
  hashWithSalt :: Int -> AggregateEvaluationResult -> Int
hashWithSalt Int
_salt AggregateEvaluationResult' {Maybe Text
Maybe POSIX
Maybe ComplianceType
Maybe EvaluationResultIdentifier
resultRecordedTime :: Maybe POSIX
evaluationResultIdentifier :: Maybe EvaluationResultIdentifier
configRuleInvokedTime :: Maybe POSIX
complianceType :: Maybe ComplianceType
awsRegion :: Maybe Text
annotation :: Maybe Text
accountId :: Maybe Text
$sel:resultRecordedTime:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe POSIX
$sel:evaluationResultIdentifier:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe EvaluationResultIdentifier
$sel:configRuleInvokedTime:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe POSIX
$sel:complianceType:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe ComplianceType
$sel:awsRegion:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe Text
$sel:annotation:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe Text
$sel:accountId:AggregateEvaluationResult' :: AggregateEvaluationResult -> 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
annotation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
awsRegion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComplianceType
complianceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
configRuleInvokedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EvaluationResultIdentifier
evaluationResultIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
resultRecordedTime

instance Prelude.NFData AggregateEvaluationResult where
  rnf :: AggregateEvaluationResult -> ()
rnf AggregateEvaluationResult' {Maybe Text
Maybe POSIX
Maybe ComplianceType
Maybe EvaluationResultIdentifier
resultRecordedTime :: Maybe POSIX
evaluationResultIdentifier :: Maybe EvaluationResultIdentifier
configRuleInvokedTime :: Maybe POSIX
complianceType :: Maybe ComplianceType
awsRegion :: Maybe Text
annotation :: Maybe Text
accountId :: Maybe Text
$sel:resultRecordedTime:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe POSIX
$sel:evaluationResultIdentifier:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe EvaluationResultIdentifier
$sel:configRuleInvokedTime:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe POSIX
$sel:complianceType:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe ComplianceType
$sel:awsRegion:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe Text
$sel:annotation:AggregateEvaluationResult' :: AggregateEvaluationResult -> Maybe Text
$sel:accountId:AggregateEvaluationResult' :: AggregateEvaluationResult -> 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
annotation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
awsRegion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComplianceType
complianceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
configRuleInvokedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EvaluationResultIdentifier
evaluationResultIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
resultRecordedTime