{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# 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.DescribeStackSetOperation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the description of the specified stack set operation.
module Amazonka.CloudFormation.DescribeStackSetOperation
  ( -- * Creating a Request
    DescribeStackSetOperation (..),
    newDescribeStackSetOperation,

    -- * Request Lenses
    describeStackSetOperation_callAs,
    describeStackSetOperation_stackSetName,
    describeStackSetOperation_operationId,

    -- * Destructuring the Response
    DescribeStackSetOperationResponse (..),
    newDescribeStackSetOperationResponse,

    -- * Response Lenses
    describeStackSetOperationResponse_stackSetOperation,
    describeStackSetOperationResponse_httpStatus,
  )
where

import Amazonka.CloudFormation.Types
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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeStackSetOperation' smart constructor.
data DescribeStackSetOperation = DescribeStackSetOperation'
  { -- | [Service-managed permissions] Specifies whether you are acting as an
    -- account administrator in the organization\'s management account or as a
    -- delegated administrator in a member account.
    --
    -- By default, @SELF@ is specified. Use @SELF@ for stack sets with
    -- self-managed permissions.
    --
    -- -   If you are signed in to the management account, specify @SELF@.
    --
    -- -   If you are signed in to a delegated administrator account, specify
    --     @DELEGATED_ADMIN@.
    --
    --     Your Amazon Web Services account must be registered as a delegated
    --     administrator in the management account. For more information, see
    --     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-orgs-delegated-admin.html Register a delegated administrator>
    --     in the /CloudFormation User Guide/.
    DescribeStackSetOperation -> Maybe CallAs
callAs :: Prelude.Maybe CallAs,
    -- | The name or the unique stack ID of the stack set for the stack
    -- operation.
    DescribeStackSetOperation -> Text
stackSetName :: Prelude.Text,
    -- | The unique ID of the stack set operation.
    DescribeStackSetOperation -> Text
operationId :: Prelude.Text
  }
  deriving (DescribeStackSetOperation -> DescribeStackSetOperation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeStackSetOperation -> DescribeStackSetOperation -> Bool
$c/= :: DescribeStackSetOperation -> DescribeStackSetOperation -> Bool
== :: DescribeStackSetOperation -> DescribeStackSetOperation -> Bool
$c== :: DescribeStackSetOperation -> DescribeStackSetOperation -> Bool
Prelude.Eq, ReadPrec [DescribeStackSetOperation]
ReadPrec DescribeStackSetOperation
Int -> ReadS DescribeStackSetOperation
ReadS [DescribeStackSetOperation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeStackSetOperation]
$creadListPrec :: ReadPrec [DescribeStackSetOperation]
readPrec :: ReadPrec DescribeStackSetOperation
$creadPrec :: ReadPrec DescribeStackSetOperation
readList :: ReadS [DescribeStackSetOperation]
$creadList :: ReadS [DescribeStackSetOperation]
readsPrec :: Int -> ReadS DescribeStackSetOperation
$creadsPrec :: Int -> ReadS DescribeStackSetOperation
Prelude.Read, Int -> DescribeStackSetOperation -> ShowS
[DescribeStackSetOperation] -> ShowS
DescribeStackSetOperation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeStackSetOperation] -> ShowS
$cshowList :: [DescribeStackSetOperation] -> ShowS
show :: DescribeStackSetOperation -> String
$cshow :: DescribeStackSetOperation -> String
showsPrec :: Int -> DescribeStackSetOperation -> ShowS
$cshowsPrec :: Int -> DescribeStackSetOperation -> ShowS
Prelude.Show, forall x.
Rep DescribeStackSetOperation x -> DescribeStackSetOperation
forall x.
DescribeStackSetOperation -> Rep DescribeStackSetOperation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeStackSetOperation x -> DescribeStackSetOperation
$cfrom :: forall x.
DescribeStackSetOperation -> Rep DescribeStackSetOperation x
Prelude.Generic)

-- |
-- Create a value of 'DescribeStackSetOperation' 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:
--
-- 'callAs', 'describeStackSetOperation_callAs' - [Service-managed permissions] Specifies whether you are acting as an
-- account administrator in the organization\'s management account or as a
-- delegated administrator in a member account.
--
-- By default, @SELF@ is specified. Use @SELF@ for stack sets with
-- self-managed permissions.
--
-- -   If you are signed in to the management account, specify @SELF@.
--
-- -   If you are signed in to a delegated administrator account, specify
--     @DELEGATED_ADMIN@.
--
--     Your Amazon Web Services account must be registered as a delegated
--     administrator in the management account. For more information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-orgs-delegated-admin.html Register a delegated administrator>
--     in the /CloudFormation User Guide/.
--
-- 'stackSetName', 'describeStackSetOperation_stackSetName' - The name or the unique stack ID of the stack set for the stack
-- operation.
--
-- 'operationId', 'describeStackSetOperation_operationId' - The unique ID of the stack set operation.
newDescribeStackSetOperation ::
  -- | 'stackSetName'
  Prelude.Text ->
  -- | 'operationId'
  Prelude.Text ->
  DescribeStackSetOperation
newDescribeStackSetOperation :: Text -> Text -> DescribeStackSetOperation
newDescribeStackSetOperation
  Text
pStackSetName_
  Text
pOperationId_ =
    DescribeStackSetOperation'
      { $sel:callAs:DescribeStackSetOperation' :: Maybe CallAs
callAs =
          forall a. Maybe a
Prelude.Nothing,
        $sel:stackSetName:DescribeStackSetOperation' :: Text
stackSetName = Text
pStackSetName_,
        $sel:operationId:DescribeStackSetOperation' :: Text
operationId = Text
pOperationId_
      }

-- | [Service-managed permissions] Specifies whether you are acting as an
-- account administrator in the organization\'s management account or as a
-- delegated administrator in a member account.
--
-- By default, @SELF@ is specified. Use @SELF@ for stack sets with
-- self-managed permissions.
--
-- -   If you are signed in to the management account, specify @SELF@.
--
-- -   If you are signed in to a delegated administrator account, specify
--     @DELEGATED_ADMIN@.
--
--     Your Amazon Web Services account must be registered as a delegated
--     administrator in the management account. For more information, see
--     <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/stacksets-orgs-delegated-admin.html Register a delegated administrator>
--     in the /CloudFormation User Guide/.
describeStackSetOperation_callAs :: Lens.Lens' DescribeStackSetOperation (Prelude.Maybe CallAs)
describeStackSetOperation_callAs :: Lens' DescribeStackSetOperation (Maybe CallAs)
describeStackSetOperation_callAs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackSetOperation' {Maybe CallAs
callAs :: Maybe CallAs
$sel:callAs:DescribeStackSetOperation' :: DescribeStackSetOperation -> Maybe CallAs
callAs} -> Maybe CallAs
callAs) (\s :: DescribeStackSetOperation
s@DescribeStackSetOperation' {} Maybe CallAs
a -> DescribeStackSetOperation
s {$sel:callAs:DescribeStackSetOperation' :: Maybe CallAs
callAs = Maybe CallAs
a} :: DescribeStackSetOperation)

-- | The name or the unique stack ID of the stack set for the stack
-- operation.
describeStackSetOperation_stackSetName :: Lens.Lens' DescribeStackSetOperation Prelude.Text
describeStackSetOperation_stackSetName :: Lens' DescribeStackSetOperation Text
describeStackSetOperation_stackSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackSetOperation' {Text
stackSetName :: Text
$sel:stackSetName:DescribeStackSetOperation' :: DescribeStackSetOperation -> Text
stackSetName} -> Text
stackSetName) (\s :: DescribeStackSetOperation
s@DescribeStackSetOperation' {} Text
a -> DescribeStackSetOperation
s {$sel:stackSetName:DescribeStackSetOperation' :: Text
stackSetName = Text
a} :: DescribeStackSetOperation)

-- | The unique ID of the stack set operation.
describeStackSetOperation_operationId :: Lens.Lens' DescribeStackSetOperation Prelude.Text
describeStackSetOperation_operationId :: Lens' DescribeStackSetOperation Text
describeStackSetOperation_operationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackSetOperation' {Text
operationId :: Text
$sel:operationId:DescribeStackSetOperation' :: DescribeStackSetOperation -> Text
operationId} -> Text
operationId) (\s :: DescribeStackSetOperation
s@DescribeStackSetOperation' {} Text
a -> DescribeStackSetOperation
s {$sel:operationId:DescribeStackSetOperation' :: Text
operationId = Text
a} :: DescribeStackSetOperation)

instance Core.AWSRequest DescribeStackSetOperation where
  type
    AWSResponse DescribeStackSetOperation =
      DescribeStackSetOperationResponse
  request :: (Service -> Service)
-> DescribeStackSetOperation -> Request DescribeStackSetOperation
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeStackSetOperation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeStackSetOperation)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"DescribeStackSetOperationResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe StackSetOperation -> Int -> DescribeStackSetOperationResponse
DescribeStackSetOperationResponse'
            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
"StackSetOperation")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DescribeStackSetOperation where
  hashWithSalt :: Int -> DescribeStackSetOperation -> Int
hashWithSalt Int
_salt DescribeStackSetOperation' {Maybe CallAs
Text
operationId :: Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:operationId:DescribeStackSetOperation' :: DescribeStackSetOperation -> Text
$sel:stackSetName:DescribeStackSetOperation' :: DescribeStackSetOperation -> Text
$sel:callAs:DescribeStackSetOperation' :: DescribeStackSetOperation -> Maybe CallAs
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CallAs
callAs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
operationId

instance Prelude.NFData DescribeStackSetOperation where
  rnf :: DescribeStackSetOperation -> ()
rnf DescribeStackSetOperation' {Maybe CallAs
Text
operationId :: Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:operationId:DescribeStackSetOperation' :: DescribeStackSetOperation -> Text
$sel:stackSetName:DescribeStackSetOperation' :: DescribeStackSetOperation -> Text
$sel:callAs:DescribeStackSetOperation' :: DescribeStackSetOperation -> Maybe CallAs
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CallAs
callAs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
stackSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
operationId

instance Data.ToHeaders DescribeStackSetOperation where
  toHeaders :: DescribeStackSetOperation -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath DescribeStackSetOperation where
  toPath :: DescribeStackSetOperation -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DescribeStackSetOperation where
  toQuery :: DescribeStackSetOperation -> QueryString
toQuery DescribeStackSetOperation' {Maybe CallAs
Text
operationId :: Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:operationId:DescribeStackSetOperation' :: DescribeStackSetOperation -> Text
$sel:stackSetName:DescribeStackSetOperation' :: DescribeStackSetOperation -> Text
$sel:callAs:DescribeStackSetOperation' :: DescribeStackSetOperation -> Maybe CallAs
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeStackSetOperation" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-15" :: Prelude.ByteString),
        ByteString
"CallAs" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe CallAs
callAs,
        ByteString
"StackSetName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
stackSetName,
        ByteString
"OperationId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
operationId
      ]

-- | /See:/ 'newDescribeStackSetOperationResponse' smart constructor.
data DescribeStackSetOperationResponse = DescribeStackSetOperationResponse'
  { -- | The specified stack set operation.
    DescribeStackSetOperationResponse -> Maybe StackSetOperation
stackSetOperation :: Prelude.Maybe StackSetOperation,
    -- | The response's http status code.
    DescribeStackSetOperationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeStackSetOperationResponse
-> DescribeStackSetOperationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeStackSetOperationResponse
-> DescribeStackSetOperationResponse -> Bool
$c/= :: DescribeStackSetOperationResponse
-> DescribeStackSetOperationResponse -> Bool
== :: DescribeStackSetOperationResponse
-> DescribeStackSetOperationResponse -> Bool
$c== :: DescribeStackSetOperationResponse
-> DescribeStackSetOperationResponse -> Bool
Prelude.Eq, ReadPrec [DescribeStackSetOperationResponse]
ReadPrec DescribeStackSetOperationResponse
Int -> ReadS DescribeStackSetOperationResponse
ReadS [DescribeStackSetOperationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeStackSetOperationResponse]
$creadListPrec :: ReadPrec [DescribeStackSetOperationResponse]
readPrec :: ReadPrec DescribeStackSetOperationResponse
$creadPrec :: ReadPrec DescribeStackSetOperationResponse
readList :: ReadS [DescribeStackSetOperationResponse]
$creadList :: ReadS [DescribeStackSetOperationResponse]
readsPrec :: Int -> ReadS DescribeStackSetOperationResponse
$creadsPrec :: Int -> ReadS DescribeStackSetOperationResponse
Prelude.Read, Int -> DescribeStackSetOperationResponse -> ShowS
[DescribeStackSetOperationResponse] -> ShowS
DescribeStackSetOperationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeStackSetOperationResponse] -> ShowS
$cshowList :: [DescribeStackSetOperationResponse] -> ShowS
show :: DescribeStackSetOperationResponse -> String
$cshow :: DescribeStackSetOperationResponse -> String
showsPrec :: Int -> DescribeStackSetOperationResponse -> ShowS
$cshowsPrec :: Int -> DescribeStackSetOperationResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeStackSetOperationResponse x
-> DescribeStackSetOperationResponse
forall x.
DescribeStackSetOperationResponse
-> Rep DescribeStackSetOperationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeStackSetOperationResponse x
-> DescribeStackSetOperationResponse
$cfrom :: forall x.
DescribeStackSetOperationResponse
-> Rep DescribeStackSetOperationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeStackSetOperationResponse' 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:
--
-- 'stackSetOperation', 'describeStackSetOperationResponse_stackSetOperation' - The specified stack set operation.
--
-- 'httpStatus', 'describeStackSetOperationResponse_httpStatus' - The response's http status code.
newDescribeStackSetOperationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeStackSetOperationResponse
newDescribeStackSetOperationResponse :: Int -> DescribeStackSetOperationResponse
newDescribeStackSetOperationResponse Int
pHttpStatus_ =
  DescribeStackSetOperationResponse'
    { $sel:stackSetOperation:DescribeStackSetOperationResponse' :: Maybe StackSetOperation
stackSetOperation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeStackSetOperationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The specified stack set operation.
describeStackSetOperationResponse_stackSetOperation :: Lens.Lens' DescribeStackSetOperationResponse (Prelude.Maybe StackSetOperation)
describeStackSetOperationResponse_stackSetOperation :: Lens' DescribeStackSetOperationResponse (Maybe StackSetOperation)
describeStackSetOperationResponse_stackSetOperation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackSetOperationResponse' {Maybe StackSetOperation
stackSetOperation :: Maybe StackSetOperation
$sel:stackSetOperation:DescribeStackSetOperationResponse' :: DescribeStackSetOperationResponse -> Maybe StackSetOperation
stackSetOperation} -> Maybe StackSetOperation
stackSetOperation) (\s :: DescribeStackSetOperationResponse
s@DescribeStackSetOperationResponse' {} Maybe StackSetOperation
a -> DescribeStackSetOperationResponse
s {$sel:stackSetOperation:DescribeStackSetOperationResponse' :: Maybe StackSetOperation
stackSetOperation = Maybe StackSetOperation
a} :: DescribeStackSetOperationResponse)

-- | The response's http status code.
describeStackSetOperationResponse_httpStatus :: Lens.Lens' DescribeStackSetOperationResponse Prelude.Int
describeStackSetOperationResponse_httpStatus :: Lens' DescribeStackSetOperationResponse Int
describeStackSetOperationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackSetOperationResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeStackSetOperationResponse' :: DescribeStackSetOperationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeStackSetOperationResponse
s@DescribeStackSetOperationResponse' {} Int
a -> DescribeStackSetOperationResponse
s {$sel:httpStatus:DescribeStackSetOperationResponse' :: Int
httpStatus = Int
a} :: DescribeStackSetOperationResponse)

instance
  Prelude.NFData
    DescribeStackSetOperationResponse
  where
  rnf :: DescribeStackSetOperationResponse -> ()
rnf DescribeStackSetOperationResponse' {Int
Maybe StackSetOperation
httpStatus :: Int
stackSetOperation :: Maybe StackSetOperation
$sel:httpStatus:DescribeStackSetOperationResponse' :: DescribeStackSetOperationResponse -> Int
$sel:stackSetOperation:DescribeStackSetOperationResponse' :: DescribeStackSetOperationResponse -> Maybe StackSetOperation
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe StackSetOperation
stackSetOperation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus