{-# 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.CloudFormation.Types.ResourceChangeDetail
-- 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.CloudFormation.Types.ResourceChangeDetail where

import Amazonka.CloudFormation.Types.ChangeSource
import Amazonka.CloudFormation.Types.EvaluationType
import Amazonka.CloudFormation.Types.ResourceTargetDefinition
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

-- | For a resource with @Modify@ as the action, the @ResourceChange@
-- structure describes the changes CloudFormation will make to that
-- resource.
--
-- /See:/ 'newResourceChangeDetail' smart constructor.
data ResourceChangeDetail = ResourceChangeDetail'
  { -- | The identity of the entity that triggered this change. This entity is a
    -- member of the group that\'s specified by the @ChangeSource@ field. For
    -- example, if you modified the value of the @KeyPairName@ parameter, the
    -- @CausingEntity@ is the name of the parameter (@KeyPairName@).
    --
    -- If the @ChangeSource@ value is @DirectModification@, no value is given
    -- for @CausingEntity@.
    ResourceChangeDetail -> Maybe Text
causingEntity :: Prelude.Maybe Prelude.Text,
    -- | The group to which the @CausingEntity@ value belongs. There are five
    -- entity groups:
    --
    -- -   @ResourceReference@ entities are @Ref@ intrinsic functions that
    --     refer to resources in the template, such as
    --     @{ \"Ref\" : \"MyEC2InstanceResource\" }@.
    --
    -- -   @ParameterReference@ entities are @Ref@ intrinsic functions that get
    --     template parameter values, such as
    --     @{ \"Ref\" : \"MyPasswordParameter\" }@.
    --
    -- -   @ResourceAttribute@ entities are @Fn::GetAtt@ intrinsic functions
    --     that get resource attribute values, such as
    --     @{ \"Fn::GetAtt\" : [ \"MyEC2InstanceResource\", \"PublicDnsName\" ] }@.
    --
    -- -   @DirectModification@ entities are changes that are made directly to
    --     the template.
    --
    -- -   @Automatic@ entities are @AWS::CloudFormation::Stack@ resource
    --     types, which are also known as nested stacks. If you made no changes
    --     to the @AWS::CloudFormation::Stack@ resource, CloudFormation sets
    --     the @ChangeSource@ to @Automatic@ because the nested stack\'s
    --     template might have changed. Changes to a nested stack\'s template
    --     aren\'t visible to CloudFormation until you run an update on the
    --     parent stack.
    ResourceChangeDetail -> Maybe ChangeSource
changeSource :: Prelude.Maybe ChangeSource,
    -- | Indicates whether CloudFormation can determine the target value, and
    -- whether the target value will change before you execute a change set.
    --
    -- For @Static@ evaluations, CloudFormation can determine that the target
    -- value will change, and its value. For example, if you directly modify
    -- the @InstanceType@ property of an EC2 instance, CloudFormation knows
    -- that this property value will change, and its value, so this is a
    -- @Static@ evaluation.
    --
    -- For @Dynamic@ evaluations, can\'t determine the target value because it
    -- depends on the result of an intrinsic function, such as a @Ref@ or
    -- @Fn::GetAtt@ intrinsic function, when the stack is updated. For example,
    -- if your template includes a reference to a resource that\'s
    -- conditionally recreated, the value of the reference (the physical ID of
    -- the resource) might change, depending on if the resource is recreated.
    -- If the resource is recreated, it will have a new physical ID, so all
    -- references to that resource will also be updated.
    ResourceChangeDetail -> Maybe EvaluationType
evaluation :: Prelude.Maybe EvaluationType,
    -- | A @ResourceTargetDefinition@ structure that describes the field that
    -- CloudFormation will change and whether the resource will be recreated.
    ResourceChangeDetail -> Maybe ResourceTargetDefinition
target :: Prelude.Maybe ResourceTargetDefinition
  }
  deriving (ResourceChangeDetail -> ResourceChangeDetail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResourceChangeDetail -> ResourceChangeDetail -> Bool
$c/= :: ResourceChangeDetail -> ResourceChangeDetail -> Bool
== :: ResourceChangeDetail -> ResourceChangeDetail -> Bool
$c== :: ResourceChangeDetail -> ResourceChangeDetail -> Bool
Prelude.Eq, ReadPrec [ResourceChangeDetail]
ReadPrec ResourceChangeDetail
Int -> ReadS ResourceChangeDetail
ReadS [ResourceChangeDetail]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResourceChangeDetail]
$creadListPrec :: ReadPrec [ResourceChangeDetail]
readPrec :: ReadPrec ResourceChangeDetail
$creadPrec :: ReadPrec ResourceChangeDetail
readList :: ReadS [ResourceChangeDetail]
$creadList :: ReadS [ResourceChangeDetail]
readsPrec :: Int -> ReadS ResourceChangeDetail
$creadsPrec :: Int -> ReadS ResourceChangeDetail
Prelude.Read, Int -> ResourceChangeDetail -> ShowS
[ResourceChangeDetail] -> ShowS
ResourceChangeDetail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResourceChangeDetail] -> ShowS
$cshowList :: [ResourceChangeDetail] -> ShowS
show :: ResourceChangeDetail -> String
$cshow :: ResourceChangeDetail -> String
showsPrec :: Int -> ResourceChangeDetail -> ShowS
$cshowsPrec :: Int -> ResourceChangeDetail -> ShowS
Prelude.Show, forall x. Rep ResourceChangeDetail x -> ResourceChangeDetail
forall x. ResourceChangeDetail -> Rep ResourceChangeDetail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResourceChangeDetail x -> ResourceChangeDetail
$cfrom :: forall x. ResourceChangeDetail -> Rep ResourceChangeDetail x
Prelude.Generic)

-- |
-- Create a value of 'ResourceChangeDetail' 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:
--
-- 'causingEntity', 'resourceChangeDetail_causingEntity' - The identity of the entity that triggered this change. This entity is a
-- member of the group that\'s specified by the @ChangeSource@ field. For
-- example, if you modified the value of the @KeyPairName@ parameter, the
-- @CausingEntity@ is the name of the parameter (@KeyPairName@).
--
-- If the @ChangeSource@ value is @DirectModification@, no value is given
-- for @CausingEntity@.
--
-- 'changeSource', 'resourceChangeDetail_changeSource' - The group to which the @CausingEntity@ value belongs. There are five
-- entity groups:
--
-- -   @ResourceReference@ entities are @Ref@ intrinsic functions that
--     refer to resources in the template, such as
--     @{ \"Ref\" : \"MyEC2InstanceResource\" }@.
--
-- -   @ParameterReference@ entities are @Ref@ intrinsic functions that get
--     template parameter values, such as
--     @{ \"Ref\" : \"MyPasswordParameter\" }@.
--
-- -   @ResourceAttribute@ entities are @Fn::GetAtt@ intrinsic functions
--     that get resource attribute values, such as
--     @{ \"Fn::GetAtt\" : [ \"MyEC2InstanceResource\", \"PublicDnsName\" ] }@.
--
-- -   @DirectModification@ entities are changes that are made directly to
--     the template.
--
-- -   @Automatic@ entities are @AWS::CloudFormation::Stack@ resource
--     types, which are also known as nested stacks. If you made no changes
--     to the @AWS::CloudFormation::Stack@ resource, CloudFormation sets
--     the @ChangeSource@ to @Automatic@ because the nested stack\'s
--     template might have changed. Changes to a nested stack\'s template
--     aren\'t visible to CloudFormation until you run an update on the
--     parent stack.
--
-- 'evaluation', 'resourceChangeDetail_evaluation' - Indicates whether CloudFormation can determine the target value, and
-- whether the target value will change before you execute a change set.
--
-- For @Static@ evaluations, CloudFormation can determine that the target
-- value will change, and its value. For example, if you directly modify
-- the @InstanceType@ property of an EC2 instance, CloudFormation knows
-- that this property value will change, and its value, so this is a
-- @Static@ evaluation.
--
-- For @Dynamic@ evaluations, can\'t determine the target value because it
-- depends on the result of an intrinsic function, such as a @Ref@ or
-- @Fn::GetAtt@ intrinsic function, when the stack is updated. For example,
-- if your template includes a reference to a resource that\'s
-- conditionally recreated, the value of the reference (the physical ID of
-- the resource) might change, depending on if the resource is recreated.
-- If the resource is recreated, it will have a new physical ID, so all
-- references to that resource will also be updated.
--
-- 'target', 'resourceChangeDetail_target' - A @ResourceTargetDefinition@ structure that describes the field that
-- CloudFormation will change and whether the resource will be recreated.
newResourceChangeDetail ::
  ResourceChangeDetail
newResourceChangeDetail :: ResourceChangeDetail
newResourceChangeDetail =
  ResourceChangeDetail'
    { $sel:causingEntity:ResourceChangeDetail' :: Maybe Text
causingEntity =
        forall a. Maybe a
Prelude.Nothing,
      $sel:changeSource:ResourceChangeDetail' :: Maybe ChangeSource
changeSource = forall a. Maybe a
Prelude.Nothing,
      $sel:evaluation:ResourceChangeDetail' :: Maybe EvaluationType
evaluation = forall a. Maybe a
Prelude.Nothing,
      $sel:target:ResourceChangeDetail' :: Maybe ResourceTargetDefinition
target = forall a. Maybe a
Prelude.Nothing
    }

-- | The identity of the entity that triggered this change. This entity is a
-- member of the group that\'s specified by the @ChangeSource@ field. For
-- example, if you modified the value of the @KeyPairName@ parameter, the
-- @CausingEntity@ is the name of the parameter (@KeyPairName@).
--
-- If the @ChangeSource@ value is @DirectModification@, no value is given
-- for @CausingEntity@.
resourceChangeDetail_causingEntity :: Lens.Lens' ResourceChangeDetail (Prelude.Maybe Prelude.Text)
resourceChangeDetail_causingEntity :: Lens' ResourceChangeDetail (Maybe Text)
resourceChangeDetail_causingEntity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChangeDetail' {Maybe Text
causingEntity :: Maybe Text
$sel:causingEntity:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe Text
causingEntity} -> Maybe Text
causingEntity) (\s :: ResourceChangeDetail
s@ResourceChangeDetail' {} Maybe Text
a -> ResourceChangeDetail
s {$sel:causingEntity:ResourceChangeDetail' :: Maybe Text
causingEntity = Maybe Text
a} :: ResourceChangeDetail)

-- | The group to which the @CausingEntity@ value belongs. There are five
-- entity groups:
--
-- -   @ResourceReference@ entities are @Ref@ intrinsic functions that
--     refer to resources in the template, such as
--     @{ \"Ref\" : \"MyEC2InstanceResource\" }@.
--
-- -   @ParameterReference@ entities are @Ref@ intrinsic functions that get
--     template parameter values, such as
--     @{ \"Ref\" : \"MyPasswordParameter\" }@.
--
-- -   @ResourceAttribute@ entities are @Fn::GetAtt@ intrinsic functions
--     that get resource attribute values, such as
--     @{ \"Fn::GetAtt\" : [ \"MyEC2InstanceResource\", \"PublicDnsName\" ] }@.
--
-- -   @DirectModification@ entities are changes that are made directly to
--     the template.
--
-- -   @Automatic@ entities are @AWS::CloudFormation::Stack@ resource
--     types, which are also known as nested stacks. If you made no changes
--     to the @AWS::CloudFormation::Stack@ resource, CloudFormation sets
--     the @ChangeSource@ to @Automatic@ because the nested stack\'s
--     template might have changed. Changes to a nested stack\'s template
--     aren\'t visible to CloudFormation until you run an update on the
--     parent stack.
resourceChangeDetail_changeSource :: Lens.Lens' ResourceChangeDetail (Prelude.Maybe ChangeSource)
resourceChangeDetail_changeSource :: Lens' ResourceChangeDetail (Maybe ChangeSource)
resourceChangeDetail_changeSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChangeDetail' {Maybe ChangeSource
changeSource :: Maybe ChangeSource
$sel:changeSource:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe ChangeSource
changeSource} -> Maybe ChangeSource
changeSource) (\s :: ResourceChangeDetail
s@ResourceChangeDetail' {} Maybe ChangeSource
a -> ResourceChangeDetail
s {$sel:changeSource:ResourceChangeDetail' :: Maybe ChangeSource
changeSource = Maybe ChangeSource
a} :: ResourceChangeDetail)

-- | Indicates whether CloudFormation can determine the target value, and
-- whether the target value will change before you execute a change set.
--
-- For @Static@ evaluations, CloudFormation can determine that the target
-- value will change, and its value. For example, if you directly modify
-- the @InstanceType@ property of an EC2 instance, CloudFormation knows
-- that this property value will change, and its value, so this is a
-- @Static@ evaluation.
--
-- For @Dynamic@ evaluations, can\'t determine the target value because it
-- depends on the result of an intrinsic function, such as a @Ref@ or
-- @Fn::GetAtt@ intrinsic function, when the stack is updated. For example,
-- if your template includes a reference to a resource that\'s
-- conditionally recreated, the value of the reference (the physical ID of
-- the resource) might change, depending on if the resource is recreated.
-- If the resource is recreated, it will have a new physical ID, so all
-- references to that resource will also be updated.
resourceChangeDetail_evaluation :: Lens.Lens' ResourceChangeDetail (Prelude.Maybe EvaluationType)
resourceChangeDetail_evaluation :: Lens' ResourceChangeDetail (Maybe EvaluationType)
resourceChangeDetail_evaluation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChangeDetail' {Maybe EvaluationType
evaluation :: Maybe EvaluationType
$sel:evaluation:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe EvaluationType
evaluation} -> Maybe EvaluationType
evaluation) (\s :: ResourceChangeDetail
s@ResourceChangeDetail' {} Maybe EvaluationType
a -> ResourceChangeDetail
s {$sel:evaluation:ResourceChangeDetail' :: Maybe EvaluationType
evaluation = Maybe EvaluationType
a} :: ResourceChangeDetail)

-- | A @ResourceTargetDefinition@ structure that describes the field that
-- CloudFormation will change and whether the resource will be recreated.
resourceChangeDetail_target :: Lens.Lens' ResourceChangeDetail (Prelude.Maybe ResourceTargetDefinition)
resourceChangeDetail_target :: Lens' ResourceChangeDetail (Maybe ResourceTargetDefinition)
resourceChangeDetail_target = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChangeDetail' {Maybe ResourceTargetDefinition
target :: Maybe ResourceTargetDefinition
$sel:target:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe ResourceTargetDefinition
target} -> Maybe ResourceTargetDefinition
target) (\s :: ResourceChangeDetail
s@ResourceChangeDetail' {} Maybe ResourceTargetDefinition
a -> ResourceChangeDetail
s {$sel:target:ResourceChangeDetail' :: Maybe ResourceTargetDefinition
target = Maybe ResourceTargetDefinition
a} :: ResourceChangeDetail)

instance Data.FromXML ResourceChangeDetail where
  parseXML :: [Node] -> Either String ResourceChangeDetail
parseXML [Node]
x =
    Maybe Text
-> Maybe ChangeSource
-> Maybe EvaluationType
-> Maybe ResourceTargetDefinition
-> ResourceChangeDetail
ResourceChangeDetail'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"CausingEntity")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ChangeSource")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Evaluation")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Target")

instance Prelude.Hashable ResourceChangeDetail where
  hashWithSalt :: Int -> ResourceChangeDetail -> Int
hashWithSalt Int
_salt ResourceChangeDetail' {Maybe Text
Maybe ChangeSource
Maybe EvaluationType
Maybe ResourceTargetDefinition
target :: Maybe ResourceTargetDefinition
evaluation :: Maybe EvaluationType
changeSource :: Maybe ChangeSource
causingEntity :: Maybe Text
$sel:target:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe ResourceTargetDefinition
$sel:evaluation:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe EvaluationType
$sel:changeSource:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe ChangeSource
$sel:causingEntity:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
causingEntity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChangeSource
changeSource
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EvaluationType
evaluation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceTargetDefinition
target

instance Prelude.NFData ResourceChangeDetail where
  rnf :: ResourceChangeDetail -> ()
rnf ResourceChangeDetail' {Maybe Text
Maybe ChangeSource
Maybe EvaluationType
Maybe ResourceTargetDefinition
target :: Maybe ResourceTargetDefinition
evaluation :: Maybe EvaluationType
changeSource :: Maybe ChangeSource
causingEntity :: Maybe Text
$sel:target:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe ResourceTargetDefinition
$sel:evaluation:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe EvaluationType
$sel:changeSource:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe ChangeSource
$sel:causingEntity:ResourceChangeDetail' :: ResourceChangeDetail -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
causingEntity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChangeSource
changeSource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EvaluationType
evaluation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceTargetDefinition
target