{-# 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.DescribeStackSet
-- 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.
module Amazonka.CloudFormation.DescribeStackSet
  ( -- * Creating a Request
    DescribeStackSet (..),
    newDescribeStackSet,

    -- * Request Lenses
    describeStackSet_callAs,
    describeStackSet_stackSetName,

    -- * Destructuring the Response
    DescribeStackSetResponse (..),
    newDescribeStackSetResponse,

    -- * Response Lenses
    describeStackSetResponse_stackSet,
    describeStackSetResponse_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:/ 'newDescribeStackSet' smart constructor.
data DescribeStackSet = DescribeStackSet'
  { -- | [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/.
    DescribeStackSet -> Maybe CallAs
callAs :: Prelude.Maybe CallAs,
    -- | The name or unique ID of the stack set whose description you want.
    DescribeStackSet -> Text
stackSetName :: Prelude.Text
  }
  deriving (DescribeStackSet -> DescribeStackSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeStackSet -> DescribeStackSet -> Bool
$c/= :: DescribeStackSet -> DescribeStackSet -> Bool
== :: DescribeStackSet -> DescribeStackSet -> Bool
$c== :: DescribeStackSet -> DescribeStackSet -> Bool
Prelude.Eq, ReadPrec [DescribeStackSet]
ReadPrec DescribeStackSet
Int -> ReadS DescribeStackSet
ReadS [DescribeStackSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeStackSet]
$creadListPrec :: ReadPrec [DescribeStackSet]
readPrec :: ReadPrec DescribeStackSet
$creadPrec :: ReadPrec DescribeStackSet
readList :: ReadS [DescribeStackSet]
$creadList :: ReadS [DescribeStackSet]
readsPrec :: Int -> ReadS DescribeStackSet
$creadsPrec :: Int -> ReadS DescribeStackSet
Prelude.Read, Int -> DescribeStackSet -> ShowS
[DescribeStackSet] -> ShowS
DescribeStackSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeStackSet] -> ShowS
$cshowList :: [DescribeStackSet] -> ShowS
show :: DescribeStackSet -> String
$cshow :: DescribeStackSet -> String
showsPrec :: Int -> DescribeStackSet -> ShowS
$cshowsPrec :: Int -> DescribeStackSet -> ShowS
Prelude.Show, forall x. Rep DescribeStackSet x -> DescribeStackSet
forall x. DescribeStackSet -> Rep DescribeStackSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeStackSet x -> DescribeStackSet
$cfrom :: forall x. DescribeStackSet -> Rep DescribeStackSet x
Prelude.Generic)

-- |
-- Create a value of 'DescribeStackSet' 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', 'describeStackSet_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', 'describeStackSet_stackSetName' - The name or unique ID of the stack set whose description you want.
newDescribeStackSet ::
  -- | 'stackSetName'
  Prelude.Text ->
  DescribeStackSet
newDescribeStackSet :: Text -> DescribeStackSet
newDescribeStackSet Text
pStackSetName_ =
  DescribeStackSet'
    { $sel:callAs:DescribeStackSet' :: Maybe CallAs
callAs = forall a. Maybe a
Prelude.Nothing,
      $sel:stackSetName:DescribeStackSet' :: Text
stackSetName = Text
pStackSetName_
    }

-- | [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/.
describeStackSet_callAs :: Lens.Lens' DescribeStackSet (Prelude.Maybe CallAs)
describeStackSet_callAs :: Lens' DescribeStackSet (Maybe CallAs)
describeStackSet_callAs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackSet' {Maybe CallAs
callAs :: Maybe CallAs
$sel:callAs:DescribeStackSet' :: DescribeStackSet -> Maybe CallAs
callAs} -> Maybe CallAs
callAs) (\s :: DescribeStackSet
s@DescribeStackSet' {} Maybe CallAs
a -> DescribeStackSet
s {$sel:callAs:DescribeStackSet' :: Maybe CallAs
callAs = Maybe CallAs
a} :: DescribeStackSet)

-- | The name or unique ID of the stack set whose description you want.
describeStackSet_stackSetName :: Lens.Lens' DescribeStackSet Prelude.Text
describeStackSet_stackSetName :: Lens' DescribeStackSet Text
describeStackSet_stackSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackSet' {Text
stackSetName :: Text
$sel:stackSetName:DescribeStackSet' :: DescribeStackSet -> Text
stackSetName} -> Text
stackSetName) (\s :: DescribeStackSet
s@DescribeStackSet' {} Text
a -> DescribeStackSet
s {$sel:stackSetName:DescribeStackSet' :: Text
stackSetName = Text
a} :: DescribeStackSet)

instance Core.AWSRequest DescribeStackSet where
  type
    AWSResponse DescribeStackSet =
      DescribeStackSetResponse
  request :: (Service -> Service)
-> DescribeStackSet -> Request DescribeStackSet
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 DescribeStackSet
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeStackSet)))
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
"DescribeStackSetResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe StackSet -> Int -> DescribeStackSetResponse
DescribeStackSetResponse'
            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
"StackSet")
            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 DescribeStackSet where
  hashWithSalt :: Int -> DescribeStackSet -> Int
hashWithSalt Int
_salt DescribeStackSet' {Maybe CallAs
Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:stackSetName:DescribeStackSet' :: DescribeStackSet -> Text
$sel:callAs:DescribeStackSet' :: DescribeStackSet -> 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

instance Prelude.NFData DescribeStackSet where
  rnf :: DescribeStackSet -> ()
rnf DescribeStackSet' {Maybe CallAs
Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:stackSetName:DescribeStackSet' :: DescribeStackSet -> Text
$sel:callAs:DescribeStackSet' :: DescribeStackSet -> 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

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

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

instance Data.ToQuery DescribeStackSet where
  toQuery :: DescribeStackSet -> QueryString
toQuery DescribeStackSet' {Maybe CallAs
Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:stackSetName:DescribeStackSet' :: DescribeStackSet -> Text
$sel:callAs:DescribeStackSet' :: DescribeStackSet -> Maybe CallAs
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeStackSet" :: 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
      ]

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

-- |
-- Create a value of 'DescribeStackSetResponse' 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:
--
-- 'stackSet', 'describeStackSetResponse_stackSet' - The specified stack set.
--
-- 'httpStatus', 'describeStackSetResponse_httpStatus' - The response's http status code.
newDescribeStackSetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeStackSetResponse
newDescribeStackSetResponse :: Int -> DescribeStackSetResponse
newDescribeStackSetResponse Int
pHttpStatus_ =
  DescribeStackSetResponse'
    { $sel:stackSet:DescribeStackSetResponse' :: Maybe StackSet
stackSet =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeStackSetResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The specified stack set.
describeStackSetResponse_stackSet :: Lens.Lens' DescribeStackSetResponse (Prelude.Maybe StackSet)
describeStackSetResponse_stackSet :: Lens' DescribeStackSetResponse (Maybe StackSet)
describeStackSetResponse_stackSet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStackSetResponse' {Maybe StackSet
stackSet :: Maybe StackSet
$sel:stackSet:DescribeStackSetResponse' :: DescribeStackSetResponse -> Maybe StackSet
stackSet} -> Maybe StackSet
stackSet) (\s :: DescribeStackSetResponse
s@DescribeStackSetResponse' {} Maybe StackSet
a -> DescribeStackSetResponse
s {$sel:stackSet:DescribeStackSetResponse' :: Maybe StackSet
stackSet = Maybe StackSet
a} :: DescribeStackSetResponse)

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

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