{-# 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.ResourceChange
-- 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.ResourceChange where

import Amazonka.CloudFormation.Types.ChangeAction
import Amazonka.CloudFormation.Types.ModuleInfo
import Amazonka.CloudFormation.Types.Replacement
import Amazonka.CloudFormation.Types.ResourceAttribute
import Amazonka.CloudFormation.Types.ResourceChangeDetail
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 @ResourceChange@ structure describes the resource and the action
-- that CloudFormation will perform on it if you execute this change set.
--
-- /See:/ 'newResourceChange' smart constructor.
data ResourceChange = ResourceChange'
  { -- | The action that CloudFormation takes on the resource, such as @Add@
    -- (adds a new resource), @Modify@ (changes a resource), @Remove@ (deletes
    -- a resource), @Import@ (imports a resource), or @Dynamic@ (exact action
    -- for the resource can\'t be determined).
    ResourceChange -> Maybe ChangeAction
action :: Prelude.Maybe ChangeAction,
    -- | The change set ID of the nested change set.
    ResourceChange -> Maybe Text
changeSetId :: Prelude.Maybe Prelude.Text,
    -- | For the @Modify@ action, a list of @ResourceChangeDetail@ structures
    -- that describes the changes that CloudFormation will make to the
    -- resource.
    ResourceChange -> Maybe [ResourceChangeDetail]
details :: Prelude.Maybe [ResourceChangeDetail],
    -- | The resource\'s logical ID, which is defined in the stack\'s template.
    ResourceChange -> Maybe Text
logicalResourceId :: Prelude.Maybe Prelude.Text,
    -- | Contains information about the module from which the resource was
    -- created, if the resource was created from a module included in the stack
    -- template.
    ResourceChange -> Maybe ModuleInfo
moduleInfo :: Prelude.Maybe ModuleInfo,
    -- | The resource\'s physical ID (resource name). Resources that you are
    -- adding don\'t have physical IDs because they haven\'t been created.
    ResourceChange -> Maybe Text
physicalResourceId :: Prelude.Maybe Prelude.Text,
    -- | For the @Modify@ action, indicates whether CloudFormation will replace
    -- the resource by creating a new one and deleting the old one. This value
    -- depends on the value of the @RequiresRecreation@ property in the
    -- @ResourceTargetDefinition@ structure. For example, if the
    -- @RequiresRecreation@ field is @Always@ and the @Evaluation@ field is
    -- @Static@, @Replacement@ is @True@. If the @RequiresRecreation@ field is
    -- @Always@ and the @Evaluation@ field is @Dynamic@, @Replacement@ is
    -- @Conditionally@.
    --
    -- If you have multiple changes with different @RequiresRecreation@ values,
    -- the @Replacement@ value depends on the change with the most impact. A
    -- @RequiresRecreation@ value of @Always@ has the most impact, followed by
    -- @Conditionally@, and then @Never@.
    ResourceChange -> Maybe Replacement
replacement :: Prelude.Maybe Replacement,
    -- | The type of CloudFormation resource, such as @AWS::S3::Bucket@.
    ResourceChange -> Maybe Text
resourceType :: Prelude.Maybe Prelude.Text,
    -- | For the @Modify@ action, indicates which resource attribute is
    -- triggering this update, such as a change in the resource attribute\'s
    -- @Metadata@, @Properties@, or @Tags@.
    ResourceChange -> Maybe [ResourceAttribute]
scope :: Prelude.Maybe [ResourceAttribute]
  }
  deriving (ResourceChange -> ResourceChange -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResourceChange -> ResourceChange -> Bool
$c/= :: ResourceChange -> ResourceChange -> Bool
== :: ResourceChange -> ResourceChange -> Bool
$c== :: ResourceChange -> ResourceChange -> Bool
Prelude.Eq, ReadPrec [ResourceChange]
ReadPrec ResourceChange
Int -> ReadS ResourceChange
ReadS [ResourceChange]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResourceChange]
$creadListPrec :: ReadPrec [ResourceChange]
readPrec :: ReadPrec ResourceChange
$creadPrec :: ReadPrec ResourceChange
readList :: ReadS [ResourceChange]
$creadList :: ReadS [ResourceChange]
readsPrec :: Int -> ReadS ResourceChange
$creadsPrec :: Int -> ReadS ResourceChange
Prelude.Read, Int -> ResourceChange -> ShowS
[ResourceChange] -> ShowS
ResourceChange -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResourceChange] -> ShowS
$cshowList :: [ResourceChange] -> ShowS
show :: ResourceChange -> String
$cshow :: ResourceChange -> String
showsPrec :: Int -> ResourceChange -> ShowS
$cshowsPrec :: Int -> ResourceChange -> ShowS
Prelude.Show, forall x. Rep ResourceChange x -> ResourceChange
forall x. ResourceChange -> Rep ResourceChange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResourceChange x -> ResourceChange
$cfrom :: forall x. ResourceChange -> Rep ResourceChange x
Prelude.Generic)

-- |
-- Create a value of 'ResourceChange' 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:
--
-- 'action', 'resourceChange_action' - The action that CloudFormation takes on the resource, such as @Add@
-- (adds a new resource), @Modify@ (changes a resource), @Remove@ (deletes
-- a resource), @Import@ (imports a resource), or @Dynamic@ (exact action
-- for the resource can\'t be determined).
--
-- 'changeSetId', 'resourceChange_changeSetId' - The change set ID of the nested change set.
--
-- 'details', 'resourceChange_details' - For the @Modify@ action, a list of @ResourceChangeDetail@ structures
-- that describes the changes that CloudFormation will make to the
-- resource.
--
-- 'logicalResourceId', 'resourceChange_logicalResourceId' - The resource\'s logical ID, which is defined in the stack\'s template.
--
-- 'moduleInfo', 'resourceChange_moduleInfo' - Contains information about the module from which the resource was
-- created, if the resource was created from a module included in the stack
-- template.
--
-- 'physicalResourceId', 'resourceChange_physicalResourceId' - The resource\'s physical ID (resource name). Resources that you are
-- adding don\'t have physical IDs because they haven\'t been created.
--
-- 'replacement', 'resourceChange_replacement' - For the @Modify@ action, indicates whether CloudFormation will replace
-- the resource by creating a new one and deleting the old one. This value
-- depends on the value of the @RequiresRecreation@ property in the
-- @ResourceTargetDefinition@ structure. For example, if the
-- @RequiresRecreation@ field is @Always@ and the @Evaluation@ field is
-- @Static@, @Replacement@ is @True@. If the @RequiresRecreation@ field is
-- @Always@ and the @Evaluation@ field is @Dynamic@, @Replacement@ is
-- @Conditionally@.
--
-- If you have multiple changes with different @RequiresRecreation@ values,
-- the @Replacement@ value depends on the change with the most impact. A
-- @RequiresRecreation@ value of @Always@ has the most impact, followed by
-- @Conditionally@, and then @Never@.
--
-- 'resourceType', 'resourceChange_resourceType' - The type of CloudFormation resource, such as @AWS::S3::Bucket@.
--
-- 'scope', 'resourceChange_scope' - For the @Modify@ action, indicates which resource attribute is
-- triggering this update, such as a change in the resource attribute\'s
-- @Metadata@, @Properties@, or @Tags@.
newResourceChange ::
  ResourceChange
newResourceChange :: ResourceChange
newResourceChange =
  ResourceChange'
    { $sel:action:ResourceChange' :: Maybe ChangeAction
action = forall a. Maybe a
Prelude.Nothing,
      $sel:changeSetId:ResourceChange' :: Maybe Text
changeSetId = forall a. Maybe a
Prelude.Nothing,
      $sel:details:ResourceChange' :: Maybe [ResourceChangeDetail]
details = forall a. Maybe a
Prelude.Nothing,
      $sel:logicalResourceId:ResourceChange' :: Maybe Text
logicalResourceId = forall a. Maybe a
Prelude.Nothing,
      $sel:moduleInfo:ResourceChange' :: Maybe ModuleInfo
moduleInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:physicalResourceId:ResourceChange' :: Maybe Text
physicalResourceId = forall a. Maybe a
Prelude.Nothing,
      $sel:replacement:ResourceChange' :: Maybe Replacement
replacement = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceType:ResourceChange' :: Maybe Text
resourceType = forall a. Maybe a
Prelude.Nothing,
      $sel:scope:ResourceChange' :: Maybe [ResourceAttribute]
scope = forall a. Maybe a
Prelude.Nothing
    }

-- | The action that CloudFormation takes on the resource, such as @Add@
-- (adds a new resource), @Modify@ (changes a resource), @Remove@ (deletes
-- a resource), @Import@ (imports a resource), or @Dynamic@ (exact action
-- for the resource can\'t be determined).
resourceChange_action :: Lens.Lens' ResourceChange (Prelude.Maybe ChangeAction)
resourceChange_action :: Lens' ResourceChange (Maybe ChangeAction)
resourceChange_action = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChange' {Maybe ChangeAction
action :: Maybe ChangeAction
$sel:action:ResourceChange' :: ResourceChange -> Maybe ChangeAction
action} -> Maybe ChangeAction
action) (\s :: ResourceChange
s@ResourceChange' {} Maybe ChangeAction
a -> ResourceChange
s {$sel:action:ResourceChange' :: Maybe ChangeAction
action = Maybe ChangeAction
a} :: ResourceChange)

-- | The change set ID of the nested change set.
resourceChange_changeSetId :: Lens.Lens' ResourceChange (Prelude.Maybe Prelude.Text)
resourceChange_changeSetId :: Lens' ResourceChange (Maybe Text)
resourceChange_changeSetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChange' {Maybe Text
changeSetId :: Maybe Text
$sel:changeSetId:ResourceChange' :: ResourceChange -> Maybe Text
changeSetId} -> Maybe Text
changeSetId) (\s :: ResourceChange
s@ResourceChange' {} Maybe Text
a -> ResourceChange
s {$sel:changeSetId:ResourceChange' :: Maybe Text
changeSetId = Maybe Text
a} :: ResourceChange)

-- | For the @Modify@ action, a list of @ResourceChangeDetail@ structures
-- that describes the changes that CloudFormation will make to the
-- resource.
resourceChange_details :: Lens.Lens' ResourceChange (Prelude.Maybe [ResourceChangeDetail])
resourceChange_details :: Lens' ResourceChange (Maybe [ResourceChangeDetail])
resourceChange_details = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChange' {Maybe [ResourceChangeDetail]
details :: Maybe [ResourceChangeDetail]
$sel:details:ResourceChange' :: ResourceChange -> Maybe [ResourceChangeDetail]
details} -> Maybe [ResourceChangeDetail]
details) (\s :: ResourceChange
s@ResourceChange' {} Maybe [ResourceChangeDetail]
a -> ResourceChange
s {$sel:details:ResourceChange' :: Maybe [ResourceChangeDetail]
details = Maybe [ResourceChangeDetail]
a} :: ResourceChange) 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 resource\'s logical ID, which is defined in the stack\'s template.
resourceChange_logicalResourceId :: Lens.Lens' ResourceChange (Prelude.Maybe Prelude.Text)
resourceChange_logicalResourceId :: Lens' ResourceChange (Maybe Text)
resourceChange_logicalResourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChange' {Maybe Text
logicalResourceId :: Maybe Text
$sel:logicalResourceId:ResourceChange' :: ResourceChange -> Maybe Text
logicalResourceId} -> Maybe Text
logicalResourceId) (\s :: ResourceChange
s@ResourceChange' {} Maybe Text
a -> ResourceChange
s {$sel:logicalResourceId:ResourceChange' :: Maybe Text
logicalResourceId = Maybe Text
a} :: ResourceChange)

-- | Contains information about the module from which the resource was
-- created, if the resource was created from a module included in the stack
-- template.
resourceChange_moduleInfo :: Lens.Lens' ResourceChange (Prelude.Maybe ModuleInfo)
resourceChange_moduleInfo :: Lens' ResourceChange (Maybe ModuleInfo)
resourceChange_moduleInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChange' {Maybe ModuleInfo
moduleInfo :: Maybe ModuleInfo
$sel:moduleInfo:ResourceChange' :: ResourceChange -> Maybe ModuleInfo
moduleInfo} -> Maybe ModuleInfo
moduleInfo) (\s :: ResourceChange
s@ResourceChange' {} Maybe ModuleInfo
a -> ResourceChange
s {$sel:moduleInfo:ResourceChange' :: Maybe ModuleInfo
moduleInfo = Maybe ModuleInfo
a} :: ResourceChange)

-- | The resource\'s physical ID (resource name). Resources that you are
-- adding don\'t have physical IDs because they haven\'t been created.
resourceChange_physicalResourceId :: Lens.Lens' ResourceChange (Prelude.Maybe Prelude.Text)
resourceChange_physicalResourceId :: Lens' ResourceChange (Maybe Text)
resourceChange_physicalResourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChange' {Maybe Text
physicalResourceId :: Maybe Text
$sel:physicalResourceId:ResourceChange' :: ResourceChange -> Maybe Text
physicalResourceId} -> Maybe Text
physicalResourceId) (\s :: ResourceChange
s@ResourceChange' {} Maybe Text
a -> ResourceChange
s {$sel:physicalResourceId:ResourceChange' :: Maybe Text
physicalResourceId = Maybe Text
a} :: ResourceChange)

-- | For the @Modify@ action, indicates whether CloudFormation will replace
-- the resource by creating a new one and deleting the old one. This value
-- depends on the value of the @RequiresRecreation@ property in the
-- @ResourceTargetDefinition@ structure. For example, if the
-- @RequiresRecreation@ field is @Always@ and the @Evaluation@ field is
-- @Static@, @Replacement@ is @True@. If the @RequiresRecreation@ field is
-- @Always@ and the @Evaluation@ field is @Dynamic@, @Replacement@ is
-- @Conditionally@.
--
-- If you have multiple changes with different @RequiresRecreation@ values,
-- the @Replacement@ value depends on the change with the most impact. A
-- @RequiresRecreation@ value of @Always@ has the most impact, followed by
-- @Conditionally@, and then @Never@.
resourceChange_replacement :: Lens.Lens' ResourceChange (Prelude.Maybe Replacement)
resourceChange_replacement :: Lens' ResourceChange (Maybe Replacement)
resourceChange_replacement = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChange' {Maybe Replacement
replacement :: Maybe Replacement
$sel:replacement:ResourceChange' :: ResourceChange -> Maybe Replacement
replacement} -> Maybe Replacement
replacement) (\s :: ResourceChange
s@ResourceChange' {} Maybe Replacement
a -> ResourceChange
s {$sel:replacement:ResourceChange' :: Maybe Replacement
replacement = Maybe Replacement
a} :: ResourceChange)

-- | The type of CloudFormation resource, such as @AWS::S3::Bucket@.
resourceChange_resourceType :: Lens.Lens' ResourceChange (Prelude.Maybe Prelude.Text)
resourceChange_resourceType :: Lens' ResourceChange (Maybe Text)
resourceChange_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChange' {Maybe Text
resourceType :: Maybe Text
$sel:resourceType:ResourceChange' :: ResourceChange -> Maybe Text
resourceType} -> Maybe Text
resourceType) (\s :: ResourceChange
s@ResourceChange' {} Maybe Text
a -> ResourceChange
s {$sel:resourceType:ResourceChange' :: Maybe Text
resourceType = Maybe Text
a} :: ResourceChange)

-- | For the @Modify@ action, indicates which resource attribute is
-- triggering this update, such as a change in the resource attribute\'s
-- @Metadata@, @Properties@, or @Tags@.
resourceChange_scope :: Lens.Lens' ResourceChange (Prelude.Maybe [ResourceAttribute])
resourceChange_scope :: Lens' ResourceChange (Maybe [ResourceAttribute])
resourceChange_scope = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceChange' {Maybe [ResourceAttribute]
scope :: Maybe [ResourceAttribute]
$sel:scope:ResourceChange' :: ResourceChange -> Maybe [ResourceAttribute]
scope} -> Maybe [ResourceAttribute]
scope) (\s :: ResourceChange
s@ResourceChange' {} Maybe [ResourceAttribute]
a -> ResourceChange
s {$sel:scope:ResourceChange' :: Maybe [ResourceAttribute]
scope = Maybe [ResourceAttribute]
a} :: ResourceChange) 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

instance Data.FromXML ResourceChange where
  parseXML :: [Node] -> Either String ResourceChange
parseXML [Node]
x =
    Maybe ChangeAction
-> Maybe Text
-> Maybe [ResourceChangeDetail]
-> Maybe Text
-> Maybe ModuleInfo
-> Maybe Text
-> Maybe Replacement
-> Maybe Text
-> Maybe [ResourceAttribute]
-> ResourceChange
ResourceChange'
      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
"Action")
      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
"ChangeSetId")
      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
"Details"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      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
"LogicalResourceId")
      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
"ModuleInfo")
      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
"PhysicalResourceId")
      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
"Replacement")
      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
"ResourceType")
      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
"Scope"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )

instance Prelude.Hashable ResourceChange where
  hashWithSalt :: Int -> ResourceChange -> Int
hashWithSalt Int
_salt ResourceChange' {Maybe [ResourceAttribute]
Maybe [ResourceChangeDetail]
Maybe Text
Maybe ChangeAction
Maybe ModuleInfo
Maybe Replacement
scope :: Maybe [ResourceAttribute]
resourceType :: Maybe Text
replacement :: Maybe Replacement
physicalResourceId :: Maybe Text
moduleInfo :: Maybe ModuleInfo
logicalResourceId :: Maybe Text
details :: Maybe [ResourceChangeDetail]
changeSetId :: Maybe Text
action :: Maybe ChangeAction
$sel:scope:ResourceChange' :: ResourceChange -> Maybe [ResourceAttribute]
$sel:resourceType:ResourceChange' :: ResourceChange -> Maybe Text
$sel:replacement:ResourceChange' :: ResourceChange -> Maybe Replacement
$sel:physicalResourceId:ResourceChange' :: ResourceChange -> Maybe Text
$sel:moduleInfo:ResourceChange' :: ResourceChange -> Maybe ModuleInfo
$sel:logicalResourceId:ResourceChange' :: ResourceChange -> Maybe Text
$sel:details:ResourceChange' :: ResourceChange -> Maybe [ResourceChangeDetail]
$sel:changeSetId:ResourceChange' :: ResourceChange -> Maybe Text
$sel:action:ResourceChange' :: ResourceChange -> Maybe ChangeAction
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChangeAction
action
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
changeSetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ResourceChangeDetail]
details
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
logicalResourceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModuleInfo
moduleInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
physicalResourceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Replacement
replacement
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ResourceAttribute]
scope

instance Prelude.NFData ResourceChange where
  rnf :: ResourceChange -> ()
rnf ResourceChange' {Maybe [ResourceAttribute]
Maybe [ResourceChangeDetail]
Maybe Text
Maybe ChangeAction
Maybe ModuleInfo
Maybe Replacement
scope :: Maybe [ResourceAttribute]
resourceType :: Maybe Text
replacement :: Maybe Replacement
physicalResourceId :: Maybe Text
moduleInfo :: Maybe ModuleInfo
logicalResourceId :: Maybe Text
details :: Maybe [ResourceChangeDetail]
changeSetId :: Maybe Text
action :: Maybe ChangeAction
$sel:scope:ResourceChange' :: ResourceChange -> Maybe [ResourceAttribute]
$sel:resourceType:ResourceChange' :: ResourceChange -> Maybe Text
$sel:replacement:ResourceChange' :: ResourceChange -> Maybe Replacement
$sel:physicalResourceId:ResourceChange' :: ResourceChange -> Maybe Text
$sel:moduleInfo:ResourceChange' :: ResourceChange -> Maybe ModuleInfo
$sel:logicalResourceId:ResourceChange' :: ResourceChange -> Maybe Text
$sel:details:ResourceChange' :: ResourceChange -> Maybe [ResourceChangeDetail]
$sel:changeSetId:ResourceChange' :: ResourceChange -> Maybe Text
$sel:action:ResourceChange' :: ResourceChange -> Maybe ChangeAction
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ChangeAction
action
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
changeSetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ResourceChangeDetail]
details
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
logicalResourceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModuleInfo
moduleInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
physicalResourceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Replacement
replacement
      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 [ResourceAttribute]
scope