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

import Amazonka.CloudFormation.Types.AutoDeployment
import Amazonka.CloudFormation.Types.ManagedExecution
import Amazonka.CloudFormation.Types.PermissionModels
import Amazonka.CloudFormation.Types.StackDriftStatus
import Amazonka.CloudFormation.Types.StackSetStatus
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 structures that contain summary information about the specified
-- stack set.
--
-- /See:/ 'newStackSetSummary' smart constructor.
data StackSetSummary = StackSetSummary'
  { -- | [Service-managed permissions] Describes whether StackSets automatically
    -- deploys to Organizations accounts that are added to a target
    -- organizational unit (OU).
    StackSetSummary -> Maybe AutoDeployment
autoDeployment :: Prelude.Maybe AutoDeployment,
    -- | A description of the stack set that you specify when the stack set is
    -- created or updated.
    StackSetSummary -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Status of the stack set\'s actual configuration compared to its expected
    -- template and parameter configuration. A stack set is considered to have
    -- drifted if one or more of its stack instances have drifted from their
    -- expected template and parameter configuration.
    --
    -- -   @DRIFTED@: One or more of the stack instances belonging to the stack
    --     set stack differs from the expected template and parameter
    --     configuration. A stack instance is considered to have drifted if one
    --     or more of the resources in the associated stack have drifted.
    --
    -- -   @NOT_CHECKED@: CloudFormation hasn\'t checked the stack set for
    --     drift.
    --
    -- -   @IN_SYNC@: All the stack instances belonging to the stack set stack
    --     match from the expected template and parameter configuration.
    --
    -- -   @UNKNOWN@: This value is reserved for future use.
    StackSetSummary -> Maybe StackDriftStatus
driftStatus :: Prelude.Maybe StackDriftStatus,
    -- | Most recent time when CloudFormation performed a drift detection
    -- operation on the stack set. This value will be @NULL@ for any stack set
    -- on which drift detection hasn\'t yet been performed.
    StackSetSummary -> Maybe ISO8601
lastDriftCheckTimestamp :: Prelude.Maybe Data.ISO8601,
    -- | Describes whether StackSets performs non-conflicting operations
    -- concurrently and queues conflicting operations.
    StackSetSummary -> Maybe ManagedExecution
managedExecution :: Prelude.Maybe ManagedExecution,
    -- | Describes how the IAM roles required for stack set operations are
    -- created.
    --
    -- -   With @self-managed@ permissions, you must create the administrator
    --     and execution roles required to deploy to target accounts. For more
    --     information, see
    --     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-prereqs-self-managed.html Grant Self-Managed Stack Set Permissions>.
    --
    -- -   With @service-managed@ permissions, StackSets automatically creates
    --     the IAM roles required to deploy to accounts managed by
    --     Organizations. For more information, see
    --     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-prereqs-service-managed.html Grant Service-Managed Stack Set Permissions>.
    StackSetSummary -> Maybe PermissionModels
permissionModel :: Prelude.Maybe PermissionModels,
    -- | The ID of the stack set.
    StackSetSummary -> Maybe Text
stackSetId :: Prelude.Maybe Prelude.Text,
    -- | The name of the stack set.
    StackSetSummary -> Maybe Text
stackSetName :: Prelude.Maybe Prelude.Text,
    -- | The status of the stack set.
    StackSetSummary -> Maybe StackSetStatus
status :: Prelude.Maybe StackSetStatus
  }
  deriving (StackSetSummary -> StackSetSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StackSetSummary -> StackSetSummary -> Bool
$c/= :: StackSetSummary -> StackSetSummary -> Bool
== :: StackSetSummary -> StackSetSummary -> Bool
$c== :: StackSetSummary -> StackSetSummary -> Bool
Prelude.Eq, ReadPrec [StackSetSummary]
ReadPrec StackSetSummary
Int -> ReadS StackSetSummary
ReadS [StackSetSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StackSetSummary]
$creadListPrec :: ReadPrec [StackSetSummary]
readPrec :: ReadPrec StackSetSummary
$creadPrec :: ReadPrec StackSetSummary
readList :: ReadS [StackSetSummary]
$creadList :: ReadS [StackSetSummary]
readsPrec :: Int -> ReadS StackSetSummary
$creadsPrec :: Int -> ReadS StackSetSummary
Prelude.Read, Int -> StackSetSummary -> ShowS
[StackSetSummary] -> ShowS
StackSetSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StackSetSummary] -> ShowS
$cshowList :: [StackSetSummary] -> ShowS
show :: StackSetSummary -> String
$cshow :: StackSetSummary -> String
showsPrec :: Int -> StackSetSummary -> ShowS
$cshowsPrec :: Int -> StackSetSummary -> ShowS
Prelude.Show, forall x. Rep StackSetSummary x -> StackSetSummary
forall x. StackSetSummary -> Rep StackSetSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StackSetSummary x -> StackSetSummary
$cfrom :: forall x. StackSetSummary -> Rep StackSetSummary x
Prelude.Generic)

-- |
-- Create a value of 'StackSetSummary' 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:
--
-- 'autoDeployment', 'stackSetSummary_autoDeployment' - [Service-managed permissions] Describes whether StackSets automatically
-- deploys to Organizations accounts that are added to a target
-- organizational unit (OU).
--
-- 'description', 'stackSetSummary_description' - A description of the stack set that you specify when the stack set is
-- created or updated.
--
-- 'driftStatus', 'stackSetSummary_driftStatus' - Status of the stack set\'s actual configuration compared to its expected
-- template and parameter configuration. A stack set is considered to have
-- drifted if one or more of its stack instances have drifted from their
-- expected template and parameter configuration.
--
-- -   @DRIFTED@: One or more of the stack instances belonging to the stack
--     set stack differs from the expected template and parameter
--     configuration. A stack instance is considered to have drifted if one
--     or more of the resources in the associated stack have drifted.
--
-- -   @NOT_CHECKED@: CloudFormation hasn\'t checked the stack set for
--     drift.
--
-- -   @IN_SYNC@: All the stack instances belonging to the stack set stack
--     match from the expected template and parameter configuration.
--
-- -   @UNKNOWN@: This value is reserved for future use.
--
-- 'lastDriftCheckTimestamp', 'stackSetSummary_lastDriftCheckTimestamp' - Most recent time when CloudFormation performed a drift detection
-- operation on the stack set. This value will be @NULL@ for any stack set
-- on which drift detection hasn\'t yet been performed.
--
-- 'managedExecution', 'stackSetSummary_managedExecution' - Describes whether StackSets performs non-conflicting operations
-- concurrently and queues conflicting operations.
--
-- 'permissionModel', 'stackSetSummary_permissionModel' - Describes how the IAM roles required for stack set operations are
-- created.
--
-- -   With @self-managed@ permissions, you must create the administrator
--     and execution roles required to deploy to target accounts. For more
--     information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-prereqs-self-managed.html Grant Self-Managed Stack Set Permissions>.
--
-- -   With @service-managed@ permissions, StackSets automatically creates
--     the IAM roles required to deploy to accounts managed by
--     Organizations. For more information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-prereqs-service-managed.html Grant Service-Managed Stack Set Permissions>.
--
-- 'stackSetId', 'stackSetSummary_stackSetId' - The ID of the stack set.
--
-- 'stackSetName', 'stackSetSummary_stackSetName' - The name of the stack set.
--
-- 'status', 'stackSetSummary_status' - The status of the stack set.
newStackSetSummary ::
  StackSetSummary
newStackSetSummary :: StackSetSummary
newStackSetSummary =
  StackSetSummary'
    { $sel:autoDeployment:StackSetSummary' :: Maybe AutoDeployment
autoDeployment = forall a. Maybe a
Prelude.Nothing,
      $sel:description:StackSetSummary' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:driftStatus:StackSetSummary' :: Maybe StackDriftStatus
driftStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:lastDriftCheckTimestamp:StackSetSummary' :: Maybe ISO8601
lastDriftCheckTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:managedExecution:StackSetSummary' :: Maybe ManagedExecution
managedExecution = forall a. Maybe a
Prelude.Nothing,
      $sel:permissionModel:StackSetSummary' :: Maybe PermissionModels
permissionModel = forall a. Maybe a
Prelude.Nothing,
      $sel:stackSetId:StackSetSummary' :: Maybe Text
stackSetId = forall a. Maybe a
Prelude.Nothing,
      $sel:stackSetName:StackSetSummary' :: Maybe Text
stackSetName = forall a. Maybe a
Prelude.Nothing,
      $sel:status:StackSetSummary' :: Maybe StackSetStatus
status = forall a. Maybe a
Prelude.Nothing
    }

-- | [Service-managed permissions] Describes whether StackSets automatically
-- deploys to Organizations accounts that are added to a target
-- organizational unit (OU).
stackSetSummary_autoDeployment :: Lens.Lens' StackSetSummary (Prelude.Maybe AutoDeployment)
stackSetSummary_autoDeployment :: Lens' StackSetSummary (Maybe AutoDeployment)
stackSetSummary_autoDeployment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackSetSummary' {Maybe AutoDeployment
autoDeployment :: Maybe AutoDeployment
$sel:autoDeployment:StackSetSummary' :: StackSetSummary -> Maybe AutoDeployment
autoDeployment} -> Maybe AutoDeployment
autoDeployment) (\s :: StackSetSummary
s@StackSetSummary' {} Maybe AutoDeployment
a -> StackSetSummary
s {$sel:autoDeployment:StackSetSummary' :: Maybe AutoDeployment
autoDeployment = Maybe AutoDeployment
a} :: StackSetSummary)

-- | A description of the stack set that you specify when the stack set is
-- created or updated.
stackSetSummary_description :: Lens.Lens' StackSetSummary (Prelude.Maybe Prelude.Text)
stackSetSummary_description :: Lens' StackSetSummary (Maybe Text)
stackSetSummary_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackSetSummary' {Maybe Text
description :: Maybe Text
$sel:description:StackSetSummary' :: StackSetSummary -> Maybe Text
description} -> Maybe Text
description) (\s :: StackSetSummary
s@StackSetSummary' {} Maybe Text
a -> StackSetSummary
s {$sel:description:StackSetSummary' :: Maybe Text
description = Maybe Text
a} :: StackSetSummary)

-- | Status of the stack set\'s actual configuration compared to its expected
-- template and parameter configuration. A stack set is considered to have
-- drifted if one or more of its stack instances have drifted from their
-- expected template and parameter configuration.
--
-- -   @DRIFTED@: One or more of the stack instances belonging to the stack
--     set stack differs from the expected template and parameter
--     configuration. A stack instance is considered to have drifted if one
--     or more of the resources in the associated stack have drifted.
--
-- -   @NOT_CHECKED@: CloudFormation hasn\'t checked the stack set for
--     drift.
--
-- -   @IN_SYNC@: All the stack instances belonging to the stack set stack
--     match from the expected template and parameter configuration.
--
-- -   @UNKNOWN@: This value is reserved for future use.
stackSetSummary_driftStatus :: Lens.Lens' StackSetSummary (Prelude.Maybe StackDriftStatus)
stackSetSummary_driftStatus :: Lens' StackSetSummary (Maybe StackDriftStatus)
stackSetSummary_driftStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackSetSummary' {Maybe StackDriftStatus
driftStatus :: Maybe StackDriftStatus
$sel:driftStatus:StackSetSummary' :: StackSetSummary -> Maybe StackDriftStatus
driftStatus} -> Maybe StackDriftStatus
driftStatus) (\s :: StackSetSummary
s@StackSetSummary' {} Maybe StackDriftStatus
a -> StackSetSummary
s {$sel:driftStatus:StackSetSummary' :: Maybe StackDriftStatus
driftStatus = Maybe StackDriftStatus
a} :: StackSetSummary)

-- | Most recent time when CloudFormation performed a drift detection
-- operation on the stack set. This value will be @NULL@ for any stack set
-- on which drift detection hasn\'t yet been performed.
stackSetSummary_lastDriftCheckTimestamp :: Lens.Lens' StackSetSummary (Prelude.Maybe Prelude.UTCTime)
stackSetSummary_lastDriftCheckTimestamp :: Lens' StackSetSummary (Maybe UTCTime)
stackSetSummary_lastDriftCheckTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackSetSummary' {Maybe ISO8601
lastDriftCheckTimestamp :: Maybe ISO8601
$sel:lastDriftCheckTimestamp:StackSetSummary' :: StackSetSummary -> Maybe ISO8601
lastDriftCheckTimestamp} -> Maybe ISO8601
lastDriftCheckTimestamp) (\s :: StackSetSummary
s@StackSetSummary' {} Maybe ISO8601
a -> StackSetSummary
s {$sel:lastDriftCheckTimestamp:StackSetSummary' :: Maybe ISO8601
lastDriftCheckTimestamp = Maybe ISO8601
a} :: StackSetSummary) 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

-- | Describes whether StackSets performs non-conflicting operations
-- concurrently and queues conflicting operations.
stackSetSummary_managedExecution :: Lens.Lens' StackSetSummary (Prelude.Maybe ManagedExecution)
stackSetSummary_managedExecution :: Lens' StackSetSummary (Maybe ManagedExecution)
stackSetSummary_managedExecution = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackSetSummary' {Maybe ManagedExecution
managedExecution :: Maybe ManagedExecution
$sel:managedExecution:StackSetSummary' :: StackSetSummary -> Maybe ManagedExecution
managedExecution} -> Maybe ManagedExecution
managedExecution) (\s :: StackSetSummary
s@StackSetSummary' {} Maybe ManagedExecution
a -> StackSetSummary
s {$sel:managedExecution:StackSetSummary' :: Maybe ManagedExecution
managedExecution = Maybe ManagedExecution
a} :: StackSetSummary)

-- | Describes how the IAM roles required for stack set operations are
-- created.
--
-- -   With @self-managed@ permissions, you must create the administrator
--     and execution roles required to deploy to target accounts. For more
--     information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-prereqs-self-managed.html Grant Self-Managed Stack Set Permissions>.
--
-- -   With @service-managed@ permissions, StackSets automatically creates
--     the IAM roles required to deploy to accounts managed by
--     Organizations. For more information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-prereqs-service-managed.html Grant Service-Managed Stack Set Permissions>.
stackSetSummary_permissionModel :: Lens.Lens' StackSetSummary (Prelude.Maybe PermissionModels)
stackSetSummary_permissionModel :: Lens' StackSetSummary (Maybe PermissionModels)
stackSetSummary_permissionModel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackSetSummary' {Maybe PermissionModels
permissionModel :: Maybe PermissionModels
$sel:permissionModel:StackSetSummary' :: StackSetSummary -> Maybe PermissionModels
permissionModel} -> Maybe PermissionModels
permissionModel) (\s :: StackSetSummary
s@StackSetSummary' {} Maybe PermissionModels
a -> StackSetSummary
s {$sel:permissionModel:StackSetSummary' :: Maybe PermissionModels
permissionModel = Maybe PermissionModels
a} :: StackSetSummary)

-- | The ID of the stack set.
stackSetSummary_stackSetId :: Lens.Lens' StackSetSummary (Prelude.Maybe Prelude.Text)
stackSetSummary_stackSetId :: Lens' StackSetSummary (Maybe Text)
stackSetSummary_stackSetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackSetSummary' {Maybe Text
stackSetId :: Maybe Text
$sel:stackSetId:StackSetSummary' :: StackSetSummary -> Maybe Text
stackSetId} -> Maybe Text
stackSetId) (\s :: StackSetSummary
s@StackSetSummary' {} Maybe Text
a -> StackSetSummary
s {$sel:stackSetId:StackSetSummary' :: Maybe Text
stackSetId = Maybe Text
a} :: StackSetSummary)

-- | The name of the stack set.
stackSetSummary_stackSetName :: Lens.Lens' StackSetSummary (Prelude.Maybe Prelude.Text)
stackSetSummary_stackSetName :: Lens' StackSetSummary (Maybe Text)
stackSetSummary_stackSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackSetSummary' {Maybe Text
stackSetName :: Maybe Text
$sel:stackSetName:StackSetSummary' :: StackSetSummary -> Maybe Text
stackSetName} -> Maybe Text
stackSetName) (\s :: StackSetSummary
s@StackSetSummary' {} Maybe Text
a -> StackSetSummary
s {$sel:stackSetName:StackSetSummary' :: Maybe Text
stackSetName = Maybe Text
a} :: StackSetSummary)

-- | The status of the stack set.
stackSetSummary_status :: Lens.Lens' StackSetSummary (Prelude.Maybe StackSetStatus)
stackSetSummary_status :: Lens' StackSetSummary (Maybe StackSetStatus)
stackSetSummary_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackSetSummary' {Maybe StackSetStatus
status :: Maybe StackSetStatus
$sel:status:StackSetSummary' :: StackSetSummary -> Maybe StackSetStatus
status} -> Maybe StackSetStatus
status) (\s :: StackSetSummary
s@StackSetSummary' {} Maybe StackSetStatus
a -> StackSetSummary
s {$sel:status:StackSetSummary' :: Maybe StackSetStatus
status = Maybe StackSetStatus
a} :: StackSetSummary)

instance Data.FromXML StackSetSummary where
  parseXML :: [Node] -> Either String StackSetSummary
parseXML [Node]
x =
    Maybe AutoDeployment
-> Maybe Text
-> Maybe StackDriftStatus
-> Maybe ISO8601
-> Maybe ManagedExecution
-> Maybe PermissionModels
-> Maybe Text
-> Maybe Text
-> Maybe StackSetStatus
-> StackSetSummary
StackSetSummary'
      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
"AutoDeployment")
      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
"DriftStatus")
      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
"LastDriftCheckTimestamp")
      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
"ManagedExecution")
      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
"PermissionModel")
      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
"StackSetId")
      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
"StackSetName")
      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")

instance Prelude.Hashable StackSetSummary where
  hashWithSalt :: Int -> StackSetSummary -> Int
hashWithSalt Int
_salt StackSetSummary' {Maybe Text
Maybe ISO8601
Maybe AutoDeployment
Maybe ManagedExecution
Maybe PermissionModels
Maybe StackDriftStatus
Maybe StackSetStatus
status :: Maybe StackSetStatus
stackSetName :: Maybe Text
stackSetId :: Maybe Text
permissionModel :: Maybe PermissionModels
managedExecution :: Maybe ManagedExecution
lastDriftCheckTimestamp :: Maybe ISO8601
driftStatus :: Maybe StackDriftStatus
description :: Maybe Text
autoDeployment :: Maybe AutoDeployment
$sel:status:StackSetSummary' :: StackSetSummary -> Maybe StackSetStatus
$sel:stackSetName:StackSetSummary' :: StackSetSummary -> Maybe Text
$sel:stackSetId:StackSetSummary' :: StackSetSummary -> Maybe Text
$sel:permissionModel:StackSetSummary' :: StackSetSummary -> Maybe PermissionModels
$sel:managedExecution:StackSetSummary' :: StackSetSummary -> Maybe ManagedExecution
$sel:lastDriftCheckTimestamp:StackSetSummary' :: StackSetSummary -> Maybe ISO8601
$sel:driftStatus:StackSetSummary' :: StackSetSummary -> Maybe StackDriftStatus
$sel:description:StackSetSummary' :: StackSetSummary -> Maybe Text
$sel:autoDeployment:StackSetSummary' :: StackSetSummary -> Maybe AutoDeployment
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AutoDeployment
autoDeployment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StackDriftStatus
driftStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
lastDriftCheckTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ManagedExecution
managedExecution
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PermissionModels
permissionModel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stackSetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stackSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StackSetStatus
status

instance Prelude.NFData StackSetSummary where
  rnf :: StackSetSummary -> ()
rnf StackSetSummary' {Maybe Text
Maybe ISO8601
Maybe AutoDeployment
Maybe ManagedExecution
Maybe PermissionModels
Maybe StackDriftStatus
Maybe StackSetStatus
status :: Maybe StackSetStatus
stackSetName :: Maybe Text
stackSetId :: Maybe Text
permissionModel :: Maybe PermissionModels
managedExecution :: Maybe ManagedExecution
lastDriftCheckTimestamp :: Maybe ISO8601
driftStatus :: Maybe StackDriftStatus
description :: Maybe Text
autoDeployment :: Maybe AutoDeployment
$sel:status:StackSetSummary' :: StackSetSummary -> Maybe StackSetStatus
$sel:stackSetName:StackSetSummary' :: StackSetSummary -> Maybe Text
$sel:stackSetId:StackSetSummary' :: StackSetSummary -> Maybe Text
$sel:permissionModel:StackSetSummary' :: StackSetSummary -> Maybe PermissionModels
$sel:managedExecution:StackSetSummary' :: StackSetSummary -> Maybe ManagedExecution
$sel:lastDriftCheckTimestamp:StackSetSummary' :: StackSetSummary -> Maybe ISO8601
$sel:driftStatus:StackSetSummary' :: StackSetSummary -> Maybe StackDriftStatus
$sel:description:StackSetSummary' :: StackSetSummary -> Maybe Text
$sel:autoDeployment:StackSetSummary' :: StackSetSummary -> Maybe AutoDeployment
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AutoDeployment
autoDeployment
      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 StackDriftStatus
driftStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
lastDriftCheckTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ManagedExecution
managedExecution
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PermissionModels
permissionModel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
stackSetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
stackSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StackSetStatus
status