{-# 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.AccountGateResult -- 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.AccountGateResult where import Amazonka.CloudFormation.Types.AccountGateStatus 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 -- | Structure that contains the results of the account gate function which -- CloudFormation invokes, if present, before proceeding with a stack set -- operation in an account and Region. -- -- For each account and Region, CloudFormation lets you specify a Lambda -- function that encapsulates any requirements that must be met before -- CloudFormation can proceed with a stack set operation in that account -- and Region. CloudFormation invokes the function each time a stack set -- operation is requested for that account and Region; if the function -- returns @FAILED@, CloudFormation cancels the operation in that account -- and Region, and sets the stack set operation result status for that -- account and Region to @FAILED@. -- -- For more information, see -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-account-gating.html Configuring a target account gate>. -- -- /See:/ 'newAccountGateResult' smart constructor. data AccountGateResult = AccountGateResult' { -- | The status of the account gate function. -- -- - @SUCCEEDED@: The account gate function has determined that the -- account and Region passes any requirements for a stack set operation -- to occur. CloudFormation proceeds with the stack operation in that -- account and Region. -- -- - @FAILED@: The account gate function has determined that the account -- and Region doesn\'t meet the requirements for a stack set operation -- to occur. CloudFormation cancels the stack set operation in that -- account and Region, and sets the stack set operation result status -- for that account and Region to @FAILED@. -- -- - @SKIPPED@: CloudFormation has skipped calling the account gate -- function for this account and Region, for one of the following -- reasons: -- -- - An account gate function hasn\'t been specified for the account -- and Region. CloudFormation proceeds with the stack set operation -- in this account and Region. -- -- - The @AWSCloudFormationStackSetExecutionRole@ of the stack set -- administration account lacks permissions to invoke the function. -- CloudFormation proceeds with the stack set operation in this -- account and Region. -- -- - Either no action is necessary, or no action is possible, on the -- stack. CloudFormation skips the stack set operation in this -- account and Region. AccountGateResult -> Maybe AccountGateStatus status :: Prelude.Maybe AccountGateStatus, -- | The reason for the account gate status assigned to this account and -- Region for the stack set operation. AccountGateResult -> Maybe Text statusReason :: Prelude.Maybe Prelude.Text } deriving (AccountGateResult -> AccountGateResult -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: AccountGateResult -> AccountGateResult -> Bool $c/= :: AccountGateResult -> AccountGateResult -> Bool == :: AccountGateResult -> AccountGateResult -> Bool $c== :: AccountGateResult -> AccountGateResult -> Bool Prelude.Eq, ReadPrec [AccountGateResult] ReadPrec AccountGateResult Int -> ReadS AccountGateResult ReadS [AccountGateResult] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [AccountGateResult] $creadListPrec :: ReadPrec [AccountGateResult] readPrec :: ReadPrec AccountGateResult $creadPrec :: ReadPrec AccountGateResult readList :: ReadS [AccountGateResult] $creadList :: ReadS [AccountGateResult] readsPrec :: Int -> ReadS AccountGateResult $creadsPrec :: Int -> ReadS AccountGateResult Prelude.Read, Int -> AccountGateResult -> ShowS [AccountGateResult] -> ShowS AccountGateResult -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [AccountGateResult] -> ShowS $cshowList :: [AccountGateResult] -> ShowS show :: AccountGateResult -> String $cshow :: AccountGateResult -> String showsPrec :: Int -> AccountGateResult -> ShowS $cshowsPrec :: Int -> AccountGateResult -> ShowS Prelude.Show, forall x. Rep AccountGateResult x -> AccountGateResult forall x. AccountGateResult -> Rep AccountGateResult x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep AccountGateResult x -> AccountGateResult $cfrom :: forall x. AccountGateResult -> Rep AccountGateResult x Prelude.Generic) -- | -- Create a value of 'AccountGateResult' 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: -- -- 'status', 'accountGateResult_status' - The status of the account gate function. -- -- - @SUCCEEDED@: The account gate function has determined that the -- account and Region passes any requirements for a stack set operation -- to occur. CloudFormation proceeds with the stack operation in that -- account and Region. -- -- - @FAILED@: The account gate function has determined that the account -- and Region doesn\'t meet the requirements for a stack set operation -- to occur. CloudFormation cancels the stack set operation in that -- account and Region, and sets the stack set operation result status -- for that account and Region to @FAILED@. -- -- - @SKIPPED@: CloudFormation has skipped calling the account gate -- function for this account and Region, for one of the following -- reasons: -- -- - An account gate function hasn\'t been specified for the account -- and Region. CloudFormation proceeds with the stack set operation -- in this account and Region. -- -- - The @AWSCloudFormationStackSetExecutionRole@ of the stack set -- administration account lacks permissions to invoke the function. -- CloudFormation proceeds with the stack set operation in this -- account and Region. -- -- - Either no action is necessary, or no action is possible, on the -- stack. CloudFormation skips the stack set operation in this -- account and Region. -- -- 'statusReason', 'accountGateResult_statusReason' - The reason for the account gate status assigned to this account and -- Region for the stack set operation. newAccountGateResult :: AccountGateResult newAccountGateResult :: AccountGateResult newAccountGateResult = AccountGateResult' { $sel:status:AccountGateResult' :: Maybe AccountGateStatus status = forall a. Maybe a Prelude.Nothing, $sel:statusReason:AccountGateResult' :: Maybe Text statusReason = forall a. Maybe a Prelude.Nothing } -- | The status of the account gate function. -- -- - @SUCCEEDED@: The account gate function has determined that the -- account and Region passes any requirements for a stack set operation -- to occur. CloudFormation proceeds with the stack operation in that -- account and Region. -- -- - @FAILED@: The account gate function has determined that the account -- and Region doesn\'t meet the requirements for a stack set operation -- to occur. CloudFormation cancels the stack set operation in that -- account and Region, and sets the stack set operation result status -- for that account and Region to @FAILED@. -- -- - @SKIPPED@: CloudFormation has skipped calling the account gate -- function for this account and Region, for one of the following -- reasons: -- -- - An account gate function hasn\'t been specified for the account -- and Region. CloudFormation proceeds with the stack set operation -- in this account and Region. -- -- - The @AWSCloudFormationStackSetExecutionRole@ of the stack set -- administration account lacks permissions to invoke the function. -- CloudFormation proceeds with the stack set operation in this -- account and Region. -- -- - Either no action is necessary, or no action is possible, on the -- stack. CloudFormation skips the stack set operation in this -- account and Region. accountGateResult_status :: Lens.Lens' AccountGateResult (Prelude.Maybe AccountGateStatus) accountGateResult_status :: Lens' AccountGateResult (Maybe AccountGateStatus) accountGateResult_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b Lens.lens (\AccountGateResult' {Maybe AccountGateStatus status :: Maybe AccountGateStatus $sel:status:AccountGateResult' :: AccountGateResult -> Maybe AccountGateStatus status} -> Maybe AccountGateStatus status) (\s :: AccountGateResult s@AccountGateResult' {} Maybe AccountGateStatus a -> AccountGateResult s {$sel:status:AccountGateResult' :: Maybe AccountGateStatus status = Maybe AccountGateStatus a} :: AccountGateResult) -- | The reason for the account gate status assigned to this account and -- Region for the stack set operation. accountGateResult_statusReason :: Lens.Lens' AccountGateResult (Prelude.Maybe Prelude.Text) accountGateResult_statusReason :: Lens' AccountGateResult (Maybe Text) accountGateResult_statusReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b Lens.lens (\AccountGateResult' {Maybe Text statusReason :: Maybe Text $sel:statusReason:AccountGateResult' :: AccountGateResult -> Maybe Text statusReason} -> Maybe Text statusReason) (\s :: AccountGateResult s@AccountGateResult' {} Maybe Text a -> AccountGateResult s {$sel:statusReason:AccountGateResult' :: Maybe Text statusReason = Maybe Text a} :: AccountGateResult) instance Data.FromXML AccountGateResult where parseXML :: [Node] -> Either String AccountGateResult parseXML [Node] x = Maybe AccountGateStatus -> Maybe Text -> AccountGateResult AccountGateResult' 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 "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 AccountGateResult where hashWithSalt :: Int -> AccountGateResult -> Int hashWithSalt Int _salt AccountGateResult' {Maybe Text Maybe AccountGateStatus statusReason :: Maybe Text status :: Maybe AccountGateStatus $sel:statusReason:AccountGateResult' :: AccountGateResult -> Maybe Text $sel:status:AccountGateResult' :: AccountGateResult -> Maybe AccountGateStatus ..} = Int _salt forall a. Hashable a => Int -> a -> Int `Prelude.hashWithSalt` Maybe AccountGateStatus status forall a. Hashable a => Int -> a -> Int `Prelude.hashWithSalt` Maybe Text statusReason instance Prelude.NFData AccountGateResult where rnf :: AccountGateResult -> () rnf AccountGateResult' {Maybe Text Maybe AccountGateStatus statusReason :: Maybe Text status :: Maybe AccountGateStatus $sel:statusReason:AccountGateResult' :: AccountGateResult -> Maybe Text $sel:status:AccountGateResult' :: AccountGateResult -> Maybe AccountGateStatus ..} = forall a. NFData a => a -> () Prelude.rnf Maybe AccountGateStatus status seq :: forall a b. a -> b -> b `Prelude.seq` forall a. NFData a => a -> () Prelude.rnf Maybe Text statusReason