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

import Amazonka.CloudFormation.Types.ChangeSetStatus
import Amazonka.CloudFormation.Types.ExecutionStatus
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 @ChangeSetSummary@ structure describes a change set, its status, and
-- the stack with which it\'s associated.
--
-- /See:/ 'newChangeSetSummary' smart constructor.
data ChangeSetSummary = ChangeSetSummary'
  { -- | The ID of the change set.
    ChangeSetSummary -> Maybe Text
changeSetId :: Prelude.Maybe Prelude.Text,
    -- | The name of the change set.
    ChangeSetSummary -> Maybe Text
changeSetName :: Prelude.Maybe Prelude.Text,
    -- | The start time when the change set was created, in UTC.
    ChangeSetSummary -> Maybe ISO8601
creationTime :: Prelude.Maybe Data.ISO8601,
    -- | Descriptive information about the change set.
    ChangeSetSummary -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | If the change set execution status is @AVAILABLE@, you can execute the
    -- change set. If you can\'t execute the change set, the status indicates
    -- why. For example, a change set might be in an @UNAVAILABLE@ state
    -- because CloudFormation is still creating it or in an @OBSOLETE@ state
    -- because the stack was already updated.
    ChangeSetSummary -> Maybe ExecutionStatus
executionStatus :: Prelude.Maybe ExecutionStatus,
    -- | Specifies the current setting of @IncludeNestedStacks@ for the change
    -- set.
    ChangeSetSummary -> Maybe Bool
includeNestedStacks :: Prelude.Maybe Prelude.Bool,
    -- | The parent change set ID.
    ChangeSetSummary -> Maybe Text
parentChangeSetId :: Prelude.Maybe Prelude.Text,
    -- | The root change set ID.
    ChangeSetSummary -> Maybe Text
rootChangeSetId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the stack with which the change set is associated.
    ChangeSetSummary -> Maybe Text
stackId :: Prelude.Maybe Prelude.Text,
    -- | The name of the stack with which the change set is associated.
    ChangeSetSummary -> Maybe Text
stackName :: Prelude.Maybe Prelude.Text,
    -- | The state of the change set, such as @CREATE_IN_PROGRESS@,
    -- @CREATE_COMPLETE@, or @FAILED@.
    ChangeSetSummary -> Maybe ChangeSetStatus
status :: Prelude.Maybe ChangeSetStatus,
    -- | A description of the change set\'s status. For example, if your change
    -- set is in the @FAILED@ state, CloudFormation shows the error message.
    ChangeSetSummary -> Maybe Text
statusReason :: Prelude.Maybe Prelude.Text
  }
  deriving (ChangeSetSummary -> ChangeSetSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChangeSetSummary -> ChangeSetSummary -> Bool
$c/= :: ChangeSetSummary -> ChangeSetSummary -> Bool
== :: ChangeSetSummary -> ChangeSetSummary -> Bool
$c== :: ChangeSetSummary -> ChangeSetSummary -> Bool
Prelude.Eq, ReadPrec [ChangeSetSummary]
ReadPrec ChangeSetSummary
Int -> ReadS ChangeSetSummary
ReadS [ChangeSetSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ChangeSetSummary]
$creadListPrec :: ReadPrec [ChangeSetSummary]
readPrec :: ReadPrec ChangeSetSummary
$creadPrec :: ReadPrec ChangeSetSummary
readList :: ReadS [ChangeSetSummary]
$creadList :: ReadS [ChangeSetSummary]
readsPrec :: Int -> ReadS ChangeSetSummary
$creadsPrec :: Int -> ReadS ChangeSetSummary
Prelude.Read, Int -> ChangeSetSummary -> ShowS
[ChangeSetSummary] -> ShowS
ChangeSetSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChangeSetSummary] -> ShowS
$cshowList :: [ChangeSetSummary] -> ShowS
show :: ChangeSetSummary -> String
$cshow :: ChangeSetSummary -> String
showsPrec :: Int -> ChangeSetSummary -> ShowS
$cshowsPrec :: Int -> ChangeSetSummary -> ShowS
Prelude.Show, forall x. Rep ChangeSetSummary x -> ChangeSetSummary
forall x. ChangeSetSummary -> Rep ChangeSetSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChangeSetSummary x -> ChangeSetSummary
$cfrom :: forall x. ChangeSetSummary -> Rep ChangeSetSummary x
Prelude.Generic)

-- |
-- Create a value of 'ChangeSetSummary' 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:
--
-- 'changeSetId', 'changeSetSummary_changeSetId' - The ID of the change set.
--
-- 'changeSetName', 'changeSetSummary_changeSetName' - The name of the change set.
--
-- 'creationTime', 'changeSetSummary_creationTime' - The start time when the change set was created, in UTC.
--
-- 'description', 'changeSetSummary_description' - Descriptive information about the change set.
--
-- 'executionStatus', 'changeSetSummary_executionStatus' - If the change set execution status is @AVAILABLE@, you can execute the
-- change set. If you can\'t execute the change set, the status indicates
-- why. For example, a change set might be in an @UNAVAILABLE@ state
-- because CloudFormation is still creating it or in an @OBSOLETE@ state
-- because the stack was already updated.
--
-- 'includeNestedStacks', 'changeSetSummary_includeNestedStacks' - Specifies the current setting of @IncludeNestedStacks@ for the change
-- set.
--
-- 'parentChangeSetId', 'changeSetSummary_parentChangeSetId' - The parent change set ID.
--
-- 'rootChangeSetId', 'changeSetSummary_rootChangeSetId' - The root change set ID.
--
-- 'stackId', 'changeSetSummary_stackId' - The ID of the stack with which the change set is associated.
--
-- 'stackName', 'changeSetSummary_stackName' - The name of the stack with which the change set is associated.
--
-- 'status', 'changeSetSummary_status' - The state of the change set, such as @CREATE_IN_PROGRESS@,
-- @CREATE_COMPLETE@, or @FAILED@.
--
-- 'statusReason', 'changeSetSummary_statusReason' - A description of the change set\'s status. For example, if your change
-- set is in the @FAILED@ state, CloudFormation shows the error message.
newChangeSetSummary ::
  ChangeSetSummary
newChangeSetSummary :: ChangeSetSummary
newChangeSetSummary =
  ChangeSetSummary'
    { $sel:changeSetId:ChangeSetSummary' :: Maybe Text
changeSetId = forall a. Maybe a
Prelude.Nothing,
      $sel:changeSetName:ChangeSetSummary' :: Maybe Text
changeSetName = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:ChangeSetSummary' :: Maybe ISO8601
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:description:ChangeSetSummary' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:executionStatus:ChangeSetSummary' :: Maybe ExecutionStatus
executionStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:includeNestedStacks:ChangeSetSummary' :: Maybe Bool
includeNestedStacks = forall a. Maybe a
Prelude.Nothing,
      $sel:parentChangeSetId:ChangeSetSummary' :: Maybe Text
parentChangeSetId = forall a. Maybe a
Prelude.Nothing,
      $sel:rootChangeSetId:ChangeSetSummary' :: Maybe Text
rootChangeSetId = forall a. Maybe a
Prelude.Nothing,
      $sel:stackId:ChangeSetSummary' :: Maybe Text
stackId = forall a. Maybe a
Prelude.Nothing,
      $sel:stackName:ChangeSetSummary' :: Maybe Text
stackName = forall a. Maybe a
Prelude.Nothing,
      $sel:status:ChangeSetSummary' :: Maybe ChangeSetStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusReason:ChangeSetSummary' :: Maybe Text
statusReason = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The name of the change set.
changeSetSummary_changeSetName :: Lens.Lens' ChangeSetSummary (Prelude.Maybe Prelude.Text)
changeSetSummary_changeSetName :: Lens' ChangeSetSummary (Maybe Text)
changeSetSummary_changeSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeSetSummary' {Maybe Text
changeSetName :: Maybe Text
$sel:changeSetName:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
changeSetName} -> Maybe Text
changeSetName) (\s :: ChangeSetSummary
s@ChangeSetSummary' {} Maybe Text
a -> ChangeSetSummary
s {$sel:changeSetName:ChangeSetSummary' :: Maybe Text
changeSetName = Maybe Text
a} :: ChangeSetSummary)

-- | The start time when the change set was created, in UTC.
changeSetSummary_creationTime :: Lens.Lens' ChangeSetSummary (Prelude.Maybe Prelude.UTCTime)
changeSetSummary_creationTime :: Lens' ChangeSetSummary (Maybe UTCTime)
changeSetSummary_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeSetSummary' {Maybe ISO8601
creationTime :: Maybe ISO8601
$sel:creationTime:ChangeSetSummary' :: ChangeSetSummary -> Maybe ISO8601
creationTime} -> Maybe ISO8601
creationTime) (\s :: ChangeSetSummary
s@ChangeSetSummary' {} Maybe ISO8601
a -> ChangeSetSummary
s {$sel:creationTime:ChangeSetSummary' :: Maybe ISO8601
creationTime = Maybe ISO8601
a} :: ChangeSetSummary) 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

-- | Descriptive information about the change set.
changeSetSummary_description :: Lens.Lens' ChangeSetSummary (Prelude.Maybe Prelude.Text)
changeSetSummary_description :: Lens' ChangeSetSummary (Maybe Text)
changeSetSummary_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeSetSummary' {Maybe Text
description :: Maybe Text
$sel:description:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
description} -> Maybe Text
description) (\s :: ChangeSetSummary
s@ChangeSetSummary' {} Maybe Text
a -> ChangeSetSummary
s {$sel:description:ChangeSetSummary' :: Maybe Text
description = Maybe Text
a} :: ChangeSetSummary)

-- | If the change set execution status is @AVAILABLE@, you can execute the
-- change set. If you can\'t execute the change set, the status indicates
-- why. For example, a change set might be in an @UNAVAILABLE@ state
-- because CloudFormation is still creating it or in an @OBSOLETE@ state
-- because the stack was already updated.
changeSetSummary_executionStatus :: Lens.Lens' ChangeSetSummary (Prelude.Maybe ExecutionStatus)
changeSetSummary_executionStatus :: Lens' ChangeSetSummary (Maybe ExecutionStatus)
changeSetSummary_executionStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeSetSummary' {Maybe ExecutionStatus
executionStatus :: Maybe ExecutionStatus
$sel:executionStatus:ChangeSetSummary' :: ChangeSetSummary -> Maybe ExecutionStatus
executionStatus} -> Maybe ExecutionStatus
executionStatus) (\s :: ChangeSetSummary
s@ChangeSetSummary' {} Maybe ExecutionStatus
a -> ChangeSetSummary
s {$sel:executionStatus:ChangeSetSummary' :: Maybe ExecutionStatus
executionStatus = Maybe ExecutionStatus
a} :: ChangeSetSummary)

-- | Specifies the current setting of @IncludeNestedStacks@ for the change
-- set.
changeSetSummary_includeNestedStacks :: Lens.Lens' ChangeSetSummary (Prelude.Maybe Prelude.Bool)
changeSetSummary_includeNestedStacks :: Lens' ChangeSetSummary (Maybe Bool)
changeSetSummary_includeNestedStacks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeSetSummary' {Maybe Bool
includeNestedStacks :: Maybe Bool
$sel:includeNestedStacks:ChangeSetSummary' :: ChangeSetSummary -> Maybe Bool
includeNestedStacks} -> Maybe Bool
includeNestedStacks) (\s :: ChangeSetSummary
s@ChangeSetSummary' {} Maybe Bool
a -> ChangeSetSummary
s {$sel:includeNestedStacks:ChangeSetSummary' :: Maybe Bool
includeNestedStacks = Maybe Bool
a} :: ChangeSetSummary)

-- | The parent change set ID.
changeSetSummary_parentChangeSetId :: Lens.Lens' ChangeSetSummary (Prelude.Maybe Prelude.Text)
changeSetSummary_parentChangeSetId :: Lens' ChangeSetSummary (Maybe Text)
changeSetSummary_parentChangeSetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeSetSummary' {Maybe Text
parentChangeSetId :: Maybe Text
$sel:parentChangeSetId:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
parentChangeSetId} -> Maybe Text
parentChangeSetId) (\s :: ChangeSetSummary
s@ChangeSetSummary' {} Maybe Text
a -> ChangeSetSummary
s {$sel:parentChangeSetId:ChangeSetSummary' :: Maybe Text
parentChangeSetId = Maybe Text
a} :: ChangeSetSummary)

-- | The root change set ID.
changeSetSummary_rootChangeSetId :: Lens.Lens' ChangeSetSummary (Prelude.Maybe Prelude.Text)
changeSetSummary_rootChangeSetId :: Lens' ChangeSetSummary (Maybe Text)
changeSetSummary_rootChangeSetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeSetSummary' {Maybe Text
rootChangeSetId :: Maybe Text
$sel:rootChangeSetId:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
rootChangeSetId} -> Maybe Text
rootChangeSetId) (\s :: ChangeSetSummary
s@ChangeSetSummary' {} Maybe Text
a -> ChangeSetSummary
s {$sel:rootChangeSetId:ChangeSetSummary' :: Maybe Text
rootChangeSetId = Maybe Text
a} :: ChangeSetSummary)

-- | The ID of the stack with which the change set is associated.
changeSetSummary_stackId :: Lens.Lens' ChangeSetSummary (Prelude.Maybe Prelude.Text)
changeSetSummary_stackId :: Lens' ChangeSetSummary (Maybe Text)
changeSetSummary_stackId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeSetSummary' {Maybe Text
stackId :: Maybe Text
$sel:stackId:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
stackId} -> Maybe Text
stackId) (\s :: ChangeSetSummary
s@ChangeSetSummary' {} Maybe Text
a -> ChangeSetSummary
s {$sel:stackId:ChangeSetSummary' :: Maybe Text
stackId = Maybe Text
a} :: ChangeSetSummary)

-- | The name of the stack with which the change set is associated.
changeSetSummary_stackName :: Lens.Lens' ChangeSetSummary (Prelude.Maybe Prelude.Text)
changeSetSummary_stackName :: Lens' ChangeSetSummary (Maybe Text)
changeSetSummary_stackName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeSetSummary' {Maybe Text
stackName :: Maybe Text
$sel:stackName:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
stackName} -> Maybe Text
stackName) (\s :: ChangeSetSummary
s@ChangeSetSummary' {} Maybe Text
a -> ChangeSetSummary
s {$sel:stackName:ChangeSetSummary' :: Maybe Text
stackName = Maybe Text
a} :: ChangeSetSummary)

-- | The state of the change set, such as @CREATE_IN_PROGRESS@,
-- @CREATE_COMPLETE@, or @FAILED@.
changeSetSummary_status :: Lens.Lens' ChangeSetSummary (Prelude.Maybe ChangeSetStatus)
changeSetSummary_status :: Lens' ChangeSetSummary (Maybe ChangeSetStatus)
changeSetSummary_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeSetSummary' {Maybe ChangeSetStatus
status :: Maybe ChangeSetStatus
$sel:status:ChangeSetSummary' :: ChangeSetSummary -> Maybe ChangeSetStatus
status} -> Maybe ChangeSetStatus
status) (\s :: ChangeSetSummary
s@ChangeSetSummary' {} Maybe ChangeSetStatus
a -> ChangeSetSummary
s {$sel:status:ChangeSetSummary' :: Maybe ChangeSetStatus
status = Maybe ChangeSetStatus
a} :: ChangeSetSummary)

-- | A description of the change set\'s status. For example, if your change
-- set is in the @FAILED@ state, CloudFormation shows the error message.
changeSetSummary_statusReason :: Lens.Lens' ChangeSetSummary (Prelude.Maybe Prelude.Text)
changeSetSummary_statusReason :: Lens' ChangeSetSummary (Maybe Text)
changeSetSummary_statusReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeSetSummary' {Maybe Text
statusReason :: Maybe Text
$sel:statusReason:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
statusReason} -> Maybe Text
statusReason) (\s :: ChangeSetSummary
s@ChangeSetSummary' {} Maybe Text
a -> ChangeSetSummary
s {$sel:statusReason:ChangeSetSummary' :: Maybe Text
statusReason = Maybe Text
a} :: ChangeSetSummary)

instance Data.FromXML ChangeSetSummary where
  parseXML :: [Node] -> Either String ChangeSetSummary
parseXML [Node]
x =
    Maybe Text
-> Maybe Text
-> Maybe ISO8601
-> Maybe Text
-> Maybe ExecutionStatus
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ChangeSetStatus
-> Maybe Text
-> ChangeSetSummary
ChangeSetSummary'
      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
"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
"ChangeSetName")
      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
"CreationTime")
      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
"Description")
      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
"ExecutionStatus")
      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
"IncludeNestedStacks")
      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
"ParentChangeSetId")
      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
"RootChangeSetId")
      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
"StackId")
      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
"StackName")
      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
"Status")
      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
"StatusReason")

instance Prelude.Hashable ChangeSetSummary where
  hashWithSalt :: Int -> ChangeSetSummary -> Int
hashWithSalt Int
_salt ChangeSetSummary' {Maybe Bool
Maybe Text
Maybe ISO8601
Maybe ChangeSetStatus
Maybe ExecutionStatus
statusReason :: Maybe Text
status :: Maybe ChangeSetStatus
stackName :: Maybe Text
stackId :: Maybe Text
rootChangeSetId :: Maybe Text
parentChangeSetId :: Maybe Text
includeNestedStacks :: Maybe Bool
executionStatus :: Maybe ExecutionStatus
description :: Maybe Text
creationTime :: Maybe ISO8601
changeSetName :: Maybe Text
changeSetId :: Maybe Text
$sel:statusReason:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:status:ChangeSetSummary' :: ChangeSetSummary -> Maybe ChangeSetStatus
$sel:stackName:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:stackId:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:rootChangeSetId:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:parentChangeSetId:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:includeNestedStacks:ChangeSetSummary' :: ChangeSetSummary -> Maybe Bool
$sel:executionStatus:ChangeSetSummary' :: ChangeSetSummary -> Maybe ExecutionStatus
$sel:description:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:creationTime:ChangeSetSummary' :: ChangeSetSummary -> Maybe ISO8601
$sel:changeSetName:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:changeSetId:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
changeSetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
changeSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExecutionStatus
executionStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
includeNestedStacks
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
parentChangeSetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
rootChangeSetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stackId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stackName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChangeSetStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
statusReason

instance Prelude.NFData ChangeSetSummary where
  rnf :: ChangeSetSummary -> ()
rnf ChangeSetSummary' {Maybe Bool
Maybe Text
Maybe ISO8601
Maybe ChangeSetStatus
Maybe ExecutionStatus
statusReason :: Maybe Text
status :: Maybe ChangeSetStatus
stackName :: Maybe Text
stackId :: Maybe Text
rootChangeSetId :: Maybe Text
parentChangeSetId :: Maybe Text
includeNestedStacks :: Maybe Bool
executionStatus :: Maybe ExecutionStatus
description :: Maybe Text
creationTime :: Maybe ISO8601
changeSetName :: Maybe Text
changeSetId :: Maybe Text
$sel:statusReason:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:status:ChangeSetSummary' :: ChangeSetSummary -> Maybe ChangeSetStatus
$sel:stackName:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:stackId:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:rootChangeSetId:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:parentChangeSetId:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:includeNestedStacks:ChangeSetSummary' :: ChangeSetSummary -> Maybe Bool
$sel:executionStatus:ChangeSetSummary' :: ChangeSetSummary -> Maybe ExecutionStatus
$sel:description:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:creationTime:ChangeSetSummary' :: ChangeSetSummary -> Maybe ISO8601
$sel:changeSetName:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
$sel:changeSetId:ChangeSetSummary' :: ChangeSetSummary -> Maybe Text
..} =
    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 Text
changeSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExecutionStatus
executionStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
includeNestedStacks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
parentChangeSetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
rootChangeSetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
stackId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
stackName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChangeSetStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusReason