{-# 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.GetTemplateSummary
-- 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 information about a new or existing template. The
-- @GetTemplateSummary@ action is useful for viewing parameter information,
-- such as default parameter values and parameter types, before you create
-- or update a stack or stack set.
--
-- You can use the @GetTemplateSummary@ action when you submit a template,
-- or you can get template information for a stack set, or a running or
-- deleted stack.
--
-- For deleted stacks, @GetTemplateSummary@ returns the template
-- information for up to 90 days after the stack has been deleted. If the
-- template doesn\'t exist, a @ValidationError@ is returned.
module Amazonka.CloudFormation.GetTemplateSummary
  ( -- * Creating a Request
    GetTemplateSummary (..),
    newGetTemplateSummary,

    -- * Request Lenses
    getTemplateSummary_callAs,
    getTemplateSummary_stackName,
    getTemplateSummary_stackSetName,
    getTemplateSummary_templateBody,
    getTemplateSummary_templateURL,

    -- * Destructuring the Response
    GetTemplateSummaryResponse (..),
    newGetTemplateSummaryResponse,

    -- * Response Lenses
    getTemplateSummaryResponse_capabilities,
    getTemplateSummaryResponse_capabilitiesReason,
    getTemplateSummaryResponse_declaredTransforms,
    getTemplateSummaryResponse_description,
    getTemplateSummaryResponse_metadata,
    getTemplateSummaryResponse_parameters,
    getTemplateSummaryResponse_resourceIdentifierSummaries,
    getTemplateSummaryResponse_resourceTypes,
    getTemplateSummaryResponse_version,
    getTemplateSummaryResponse_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

-- | The input for the GetTemplateSummary action.
--
-- /See:/ 'newGetTemplateSummary' smart constructor.
data GetTemplateSummary = GetTemplateSummary'
  { -- | [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/.
    GetTemplateSummary -> Maybe CallAs
callAs :: Prelude.Maybe CallAs,
    -- | The name or the stack ID that\'s associated with the stack, which
    -- aren\'t always interchangeable. For running stacks, you can specify
    -- either the stack\'s name or its unique stack ID. For deleted stack, you
    -- must specify the unique stack ID.
    --
    -- Conditional: You must specify only one of the following parameters:
    -- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
    GetTemplateSummary -> Maybe Text
stackName :: Prelude.Maybe Prelude.Text,
    -- | The name or unique ID of the stack set from which the stack was created.
    --
    -- Conditional: You must specify only one of the following parameters:
    -- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
    GetTemplateSummary -> Maybe Text
stackSetName :: Prelude.Maybe Prelude.Text,
    -- | Structure containing the template body with a minimum length of 1 byte
    -- and a maximum length of 51,200 bytes. For more information about
    -- templates, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/template-anatomy.html Template anatomy>
    -- in the CloudFormation User Guide.
    --
    -- Conditional: You must specify only one of the following parameters:
    -- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
    GetTemplateSummary -> Maybe Text
templateBody :: Prelude.Maybe Prelude.Text,
    -- | Location of file containing the template body. The URL must point to a
    -- template (max size: 460,800 bytes) that\'s located in an Amazon S3
    -- bucket or a Systems Manager document. For more information about
    -- templates, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/template-anatomy.html Template anatomy>
    -- in the CloudFormation User Guide.
    --
    -- Conditional: You must specify only one of the following parameters:
    -- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
    GetTemplateSummary -> Maybe Text
templateURL :: Prelude.Maybe Prelude.Text
  }
  deriving (GetTemplateSummary -> GetTemplateSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTemplateSummary -> GetTemplateSummary -> Bool
$c/= :: GetTemplateSummary -> GetTemplateSummary -> Bool
== :: GetTemplateSummary -> GetTemplateSummary -> Bool
$c== :: GetTemplateSummary -> GetTemplateSummary -> Bool
Prelude.Eq, ReadPrec [GetTemplateSummary]
ReadPrec GetTemplateSummary
Int -> ReadS GetTemplateSummary
ReadS [GetTemplateSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTemplateSummary]
$creadListPrec :: ReadPrec [GetTemplateSummary]
readPrec :: ReadPrec GetTemplateSummary
$creadPrec :: ReadPrec GetTemplateSummary
readList :: ReadS [GetTemplateSummary]
$creadList :: ReadS [GetTemplateSummary]
readsPrec :: Int -> ReadS GetTemplateSummary
$creadsPrec :: Int -> ReadS GetTemplateSummary
Prelude.Read, Int -> GetTemplateSummary -> ShowS
[GetTemplateSummary] -> ShowS
GetTemplateSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTemplateSummary] -> ShowS
$cshowList :: [GetTemplateSummary] -> ShowS
show :: GetTemplateSummary -> String
$cshow :: GetTemplateSummary -> String
showsPrec :: Int -> GetTemplateSummary -> ShowS
$cshowsPrec :: Int -> GetTemplateSummary -> ShowS
Prelude.Show, forall x. Rep GetTemplateSummary x -> GetTemplateSummary
forall x. GetTemplateSummary -> Rep GetTemplateSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTemplateSummary x -> GetTemplateSummary
$cfrom :: forall x. GetTemplateSummary -> Rep GetTemplateSummary x
Prelude.Generic)

-- |
-- Create a value of 'GetTemplateSummary' 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', 'getTemplateSummary_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/.
--
-- 'stackName', 'getTemplateSummary_stackName' - The name or the stack ID that\'s associated with the stack, which
-- aren\'t always interchangeable. For running stacks, you can specify
-- either the stack\'s name or its unique stack ID. For deleted stack, you
-- must specify the unique stack ID.
--
-- Conditional: You must specify only one of the following parameters:
-- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
--
-- 'stackSetName', 'getTemplateSummary_stackSetName' - The name or unique ID of the stack set from which the stack was created.
--
-- Conditional: You must specify only one of the following parameters:
-- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
--
-- 'templateBody', 'getTemplateSummary_templateBody' - Structure containing the template body with a minimum length of 1 byte
-- and a maximum length of 51,200 bytes. For more information about
-- templates, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/template-anatomy.html Template anatomy>
-- in the CloudFormation User Guide.
--
-- Conditional: You must specify only one of the following parameters:
-- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
--
-- 'templateURL', 'getTemplateSummary_templateURL' - Location of file containing the template body. The URL must point to a
-- template (max size: 460,800 bytes) that\'s located in an Amazon S3
-- bucket or a Systems Manager document. For more information about
-- templates, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/template-anatomy.html Template anatomy>
-- in the CloudFormation User Guide.
--
-- Conditional: You must specify only one of the following parameters:
-- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
newGetTemplateSummary ::
  GetTemplateSummary
newGetTemplateSummary :: GetTemplateSummary
newGetTemplateSummary =
  GetTemplateSummary'
    { $sel:callAs:GetTemplateSummary' :: Maybe CallAs
callAs = forall a. Maybe a
Prelude.Nothing,
      $sel:stackName:GetTemplateSummary' :: Maybe Text
stackName = forall a. Maybe a
Prelude.Nothing,
      $sel:stackSetName:GetTemplateSummary' :: Maybe Text
stackSetName = forall a. Maybe a
Prelude.Nothing,
      $sel:templateBody:GetTemplateSummary' :: Maybe Text
templateBody = forall a. Maybe a
Prelude.Nothing,
      $sel:templateURL:GetTemplateSummary' :: Maybe Text
templateURL = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The name or the stack ID that\'s associated with the stack, which
-- aren\'t always interchangeable. For running stacks, you can specify
-- either the stack\'s name or its unique stack ID. For deleted stack, you
-- must specify the unique stack ID.
--
-- Conditional: You must specify only one of the following parameters:
-- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
getTemplateSummary_stackName :: Lens.Lens' GetTemplateSummary (Prelude.Maybe Prelude.Text)
getTemplateSummary_stackName :: Lens' GetTemplateSummary (Maybe Text)
getTemplateSummary_stackName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummary' {Maybe Text
stackName :: Maybe Text
$sel:stackName:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
stackName} -> Maybe Text
stackName) (\s :: GetTemplateSummary
s@GetTemplateSummary' {} Maybe Text
a -> GetTemplateSummary
s {$sel:stackName:GetTemplateSummary' :: Maybe Text
stackName = Maybe Text
a} :: GetTemplateSummary)

-- | The name or unique ID of the stack set from which the stack was created.
--
-- Conditional: You must specify only one of the following parameters:
-- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
getTemplateSummary_stackSetName :: Lens.Lens' GetTemplateSummary (Prelude.Maybe Prelude.Text)
getTemplateSummary_stackSetName :: Lens' GetTemplateSummary (Maybe Text)
getTemplateSummary_stackSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummary' {Maybe Text
stackSetName :: Maybe Text
$sel:stackSetName:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
stackSetName} -> Maybe Text
stackSetName) (\s :: GetTemplateSummary
s@GetTemplateSummary' {} Maybe Text
a -> GetTemplateSummary
s {$sel:stackSetName:GetTemplateSummary' :: Maybe Text
stackSetName = Maybe Text
a} :: GetTemplateSummary)

-- | Structure containing the template body with a minimum length of 1 byte
-- and a maximum length of 51,200 bytes. For more information about
-- templates, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/template-anatomy.html Template anatomy>
-- in the CloudFormation User Guide.
--
-- Conditional: You must specify only one of the following parameters:
-- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
getTemplateSummary_templateBody :: Lens.Lens' GetTemplateSummary (Prelude.Maybe Prelude.Text)
getTemplateSummary_templateBody :: Lens' GetTemplateSummary (Maybe Text)
getTemplateSummary_templateBody = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummary' {Maybe Text
templateBody :: Maybe Text
$sel:templateBody:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
templateBody} -> Maybe Text
templateBody) (\s :: GetTemplateSummary
s@GetTemplateSummary' {} Maybe Text
a -> GetTemplateSummary
s {$sel:templateBody:GetTemplateSummary' :: Maybe Text
templateBody = Maybe Text
a} :: GetTemplateSummary)

-- | Location of file containing the template body. The URL must point to a
-- template (max size: 460,800 bytes) that\'s located in an Amazon S3
-- bucket or a Systems Manager document. For more information about
-- templates, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/template-anatomy.html Template anatomy>
-- in the CloudFormation User Guide.
--
-- Conditional: You must specify only one of the following parameters:
-- @StackName@, @StackSetName@, @TemplateBody@, or @TemplateURL@.
getTemplateSummary_templateURL :: Lens.Lens' GetTemplateSummary (Prelude.Maybe Prelude.Text)
getTemplateSummary_templateURL :: Lens' GetTemplateSummary (Maybe Text)
getTemplateSummary_templateURL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummary' {Maybe Text
templateURL :: Maybe Text
$sel:templateURL:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
templateURL} -> Maybe Text
templateURL) (\s :: GetTemplateSummary
s@GetTemplateSummary' {} Maybe Text
a -> GetTemplateSummary
s {$sel:templateURL:GetTemplateSummary' :: Maybe Text
templateURL = Maybe Text
a} :: GetTemplateSummary)

instance Core.AWSRequest GetTemplateSummary where
  type
    AWSResponse GetTemplateSummary =
      GetTemplateSummaryResponse
  request :: (Service -> Service)
-> GetTemplateSummary -> Request GetTemplateSummary
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 GetTemplateSummary
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetTemplateSummary)))
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
"GetTemplateSummaryResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [Capability]
-> Maybe Text
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Maybe [ParameterDeclaration]
-> Maybe [ResourceIdentifierSummary]
-> Maybe [Text]
-> Maybe Text
-> Int
-> GetTemplateSummaryResponse
GetTemplateSummaryResponse'
            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
"Capabilities"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            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
"CapabilitiesReason")
            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
"DeclaredTransforms"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            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
"Metadata")
            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
"Parameters"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            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
"ResourceIdentifierSummaries"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            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
"ResourceTypes"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            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
"Version")
            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 GetTemplateSummary where
  hashWithSalt :: Int -> GetTemplateSummary -> Int
hashWithSalt Int
_salt GetTemplateSummary' {Maybe Text
Maybe CallAs
templateURL :: Maybe Text
templateBody :: Maybe Text
stackSetName :: Maybe Text
stackName :: Maybe Text
callAs :: Maybe CallAs
$sel:templateURL:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:templateBody:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:stackSetName:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:stackName:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:callAs:GetTemplateSummary' :: GetTemplateSummary -> 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` Maybe Text
stackName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stackSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
templateBody
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
templateURL

instance Prelude.NFData GetTemplateSummary where
  rnf :: GetTemplateSummary -> ()
rnf GetTemplateSummary' {Maybe Text
Maybe CallAs
templateURL :: Maybe Text
templateBody :: Maybe Text
stackSetName :: Maybe Text
stackName :: Maybe Text
callAs :: Maybe CallAs
$sel:templateURL:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:templateBody:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:stackSetName:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:stackName:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:callAs:GetTemplateSummary' :: GetTemplateSummary -> 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 Maybe Text
stackName
      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 Text
templateBody
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
templateURL

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

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

instance Data.ToQuery GetTemplateSummary where
  toQuery :: GetTemplateSummary -> QueryString
toQuery GetTemplateSummary' {Maybe Text
Maybe CallAs
templateURL :: Maybe Text
templateBody :: Maybe Text
stackSetName :: Maybe Text
stackName :: Maybe Text
callAs :: Maybe CallAs
$sel:templateURL:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:templateBody:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:stackSetName:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:stackName:GetTemplateSummary' :: GetTemplateSummary -> Maybe Text
$sel:callAs:GetTemplateSummary' :: GetTemplateSummary -> Maybe CallAs
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetTemplateSummary" :: 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
"StackName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
stackName,
        ByteString
"StackSetName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
stackSetName,
        ByteString
"TemplateBody" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
templateBody,
        ByteString
"TemplateURL" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
templateURL
      ]

-- | The output for the GetTemplateSummary action.
--
-- /See:/ 'newGetTemplateSummaryResponse' smart constructor.
data GetTemplateSummaryResponse = GetTemplateSummaryResponse'
  { -- | The capabilities found within the template. If your template contains
    -- IAM resources, you must specify the @CAPABILITY_IAM@ or
    -- @CAPABILITY_NAMED_IAM@ value for this parameter when you use the
    -- CreateStack or UpdateStack actions with your template; otherwise, those
    -- actions return an @InsufficientCapabilities@ error.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/using-iam-template.html#capabilities Acknowledging IAM Resources in CloudFormation Templates>.
    GetTemplateSummaryResponse -> Maybe [Capability]
capabilities :: Prelude.Maybe [Capability],
    -- | The list of resources that generated the values in the @Capabilities@
    -- response element.
    GetTemplateSummaryResponse -> Maybe Text
capabilitiesReason :: Prelude.Maybe Prelude.Text,
    -- | A list of the transforms that are declared in the template.
    GetTemplateSummaryResponse -> Maybe [Text]
declaredTransforms :: Prelude.Maybe [Prelude.Text],
    -- | The value that\'s defined in the @Description@ property of the template.
    GetTemplateSummaryResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The value that\'s defined for the @Metadata@ property of the template.
    GetTemplateSummaryResponse -> Maybe Text
metadata :: Prelude.Maybe Prelude.Text,
    -- | A list of parameter declarations that describe various properties for
    -- each parameter.
    GetTemplateSummaryResponse -> Maybe [ParameterDeclaration]
parameters :: Prelude.Maybe [ParameterDeclaration],
    -- | A list of resource identifier summaries that describe the target
    -- resources of an import operation and the properties you can provide
    -- during the import to identify the target resources. For example,
    -- @BucketName@ is a possible identifier property for an @AWS::S3::Bucket@
    -- resource.
    GetTemplateSummaryResponse -> Maybe [ResourceIdentifierSummary]
resourceIdentifierSummaries :: Prelude.Maybe [ResourceIdentifierSummary],
    -- | A list of all the template resource types that are defined in the
    -- template, such as @AWS::EC2::Instance@, @AWS::Dynamo::Table@, and
    -- @Custom::MyCustomInstance@.
    GetTemplateSummaryResponse -> Maybe [Text]
resourceTypes :: Prelude.Maybe [Prelude.Text],
    -- | The Amazon Web Services template format version, which identifies the
    -- capabilities of the template.
    GetTemplateSummaryResponse -> Maybe Text
version :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetTemplateSummaryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetTemplateSummaryResponse -> GetTemplateSummaryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTemplateSummaryResponse -> GetTemplateSummaryResponse -> Bool
$c/= :: GetTemplateSummaryResponse -> GetTemplateSummaryResponse -> Bool
== :: GetTemplateSummaryResponse -> GetTemplateSummaryResponse -> Bool
$c== :: GetTemplateSummaryResponse -> GetTemplateSummaryResponse -> Bool
Prelude.Eq, ReadPrec [GetTemplateSummaryResponse]
ReadPrec GetTemplateSummaryResponse
Int -> ReadS GetTemplateSummaryResponse
ReadS [GetTemplateSummaryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTemplateSummaryResponse]
$creadListPrec :: ReadPrec [GetTemplateSummaryResponse]
readPrec :: ReadPrec GetTemplateSummaryResponse
$creadPrec :: ReadPrec GetTemplateSummaryResponse
readList :: ReadS [GetTemplateSummaryResponse]
$creadList :: ReadS [GetTemplateSummaryResponse]
readsPrec :: Int -> ReadS GetTemplateSummaryResponse
$creadsPrec :: Int -> ReadS GetTemplateSummaryResponse
Prelude.Read, Int -> GetTemplateSummaryResponse -> ShowS
[GetTemplateSummaryResponse] -> ShowS
GetTemplateSummaryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTemplateSummaryResponse] -> ShowS
$cshowList :: [GetTemplateSummaryResponse] -> ShowS
show :: GetTemplateSummaryResponse -> String
$cshow :: GetTemplateSummaryResponse -> String
showsPrec :: Int -> GetTemplateSummaryResponse -> ShowS
$cshowsPrec :: Int -> GetTemplateSummaryResponse -> ShowS
Prelude.Show, forall x.
Rep GetTemplateSummaryResponse x -> GetTemplateSummaryResponse
forall x.
GetTemplateSummaryResponse -> Rep GetTemplateSummaryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetTemplateSummaryResponse x -> GetTemplateSummaryResponse
$cfrom :: forall x.
GetTemplateSummaryResponse -> Rep GetTemplateSummaryResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetTemplateSummaryResponse' 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:
--
-- 'capabilities', 'getTemplateSummaryResponse_capabilities' - The capabilities found within the template. If your template contains
-- IAM resources, you must specify the @CAPABILITY_IAM@ or
-- @CAPABILITY_NAMED_IAM@ value for this parameter when you use the
-- CreateStack or UpdateStack actions with your template; otherwise, those
-- actions return an @InsufficientCapabilities@ error.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/using-iam-template.html#capabilities Acknowledging IAM Resources in CloudFormation Templates>.
--
-- 'capabilitiesReason', 'getTemplateSummaryResponse_capabilitiesReason' - The list of resources that generated the values in the @Capabilities@
-- response element.
--
-- 'declaredTransforms', 'getTemplateSummaryResponse_declaredTransforms' - A list of the transforms that are declared in the template.
--
-- 'description', 'getTemplateSummaryResponse_description' - The value that\'s defined in the @Description@ property of the template.
--
-- 'metadata', 'getTemplateSummaryResponse_metadata' - The value that\'s defined for the @Metadata@ property of the template.
--
-- 'parameters', 'getTemplateSummaryResponse_parameters' - A list of parameter declarations that describe various properties for
-- each parameter.
--
-- 'resourceIdentifierSummaries', 'getTemplateSummaryResponse_resourceIdentifierSummaries' - A list of resource identifier summaries that describe the target
-- resources of an import operation and the properties you can provide
-- during the import to identify the target resources. For example,
-- @BucketName@ is a possible identifier property for an @AWS::S3::Bucket@
-- resource.
--
-- 'resourceTypes', 'getTemplateSummaryResponse_resourceTypes' - A list of all the template resource types that are defined in the
-- template, such as @AWS::EC2::Instance@, @AWS::Dynamo::Table@, and
-- @Custom::MyCustomInstance@.
--
-- 'version', 'getTemplateSummaryResponse_version' - The Amazon Web Services template format version, which identifies the
-- capabilities of the template.
--
-- 'httpStatus', 'getTemplateSummaryResponse_httpStatus' - The response's http status code.
newGetTemplateSummaryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetTemplateSummaryResponse
newGetTemplateSummaryResponse :: Int -> GetTemplateSummaryResponse
newGetTemplateSummaryResponse Int
pHttpStatus_ =
  GetTemplateSummaryResponse'
    { $sel:capabilities:GetTemplateSummaryResponse' :: Maybe [Capability]
capabilities =
        forall a. Maybe a
Prelude.Nothing,
      $sel:capabilitiesReason:GetTemplateSummaryResponse' :: Maybe Text
capabilitiesReason = forall a. Maybe a
Prelude.Nothing,
      $sel:declaredTransforms:GetTemplateSummaryResponse' :: Maybe [Text]
declaredTransforms = forall a. Maybe a
Prelude.Nothing,
      $sel:description:GetTemplateSummaryResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:metadata:GetTemplateSummaryResponse' :: Maybe Text
metadata = forall a. Maybe a
Prelude.Nothing,
      $sel:parameters:GetTemplateSummaryResponse' :: Maybe [ParameterDeclaration]
parameters = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceIdentifierSummaries:GetTemplateSummaryResponse' :: Maybe [ResourceIdentifierSummary]
resourceIdentifierSummaries = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceTypes:GetTemplateSummaryResponse' :: Maybe [Text]
resourceTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:version:GetTemplateSummaryResponse' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetTemplateSummaryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The capabilities found within the template. If your template contains
-- IAM resources, you must specify the @CAPABILITY_IAM@ or
-- @CAPABILITY_NAMED_IAM@ value for this parameter when you use the
-- CreateStack or UpdateStack actions with your template; otherwise, those
-- actions return an @InsufficientCapabilities@ error.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/using-iam-template.html#capabilities Acknowledging IAM Resources in CloudFormation Templates>.
getTemplateSummaryResponse_capabilities :: Lens.Lens' GetTemplateSummaryResponse (Prelude.Maybe [Capability])
getTemplateSummaryResponse_capabilities :: Lens' GetTemplateSummaryResponse (Maybe [Capability])
getTemplateSummaryResponse_capabilities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummaryResponse' {Maybe [Capability]
capabilities :: Maybe [Capability]
$sel:capabilities:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe [Capability]
capabilities} -> Maybe [Capability]
capabilities) (\s :: GetTemplateSummaryResponse
s@GetTemplateSummaryResponse' {} Maybe [Capability]
a -> GetTemplateSummaryResponse
s {$sel:capabilities:GetTemplateSummaryResponse' :: Maybe [Capability]
capabilities = Maybe [Capability]
a} :: GetTemplateSummaryResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The list of resources that generated the values in the @Capabilities@
-- response element.
getTemplateSummaryResponse_capabilitiesReason :: Lens.Lens' GetTemplateSummaryResponse (Prelude.Maybe Prelude.Text)
getTemplateSummaryResponse_capabilitiesReason :: Lens' GetTemplateSummaryResponse (Maybe Text)
getTemplateSummaryResponse_capabilitiesReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummaryResponse' {Maybe Text
capabilitiesReason :: Maybe Text
$sel:capabilitiesReason:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe Text
capabilitiesReason} -> Maybe Text
capabilitiesReason) (\s :: GetTemplateSummaryResponse
s@GetTemplateSummaryResponse' {} Maybe Text
a -> GetTemplateSummaryResponse
s {$sel:capabilitiesReason:GetTemplateSummaryResponse' :: Maybe Text
capabilitiesReason = Maybe Text
a} :: GetTemplateSummaryResponse)

-- | A list of the transforms that are declared in the template.
getTemplateSummaryResponse_declaredTransforms :: Lens.Lens' GetTemplateSummaryResponse (Prelude.Maybe [Prelude.Text])
getTemplateSummaryResponse_declaredTransforms :: Lens' GetTemplateSummaryResponse (Maybe [Text])
getTemplateSummaryResponse_declaredTransforms = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummaryResponse' {Maybe [Text]
declaredTransforms :: Maybe [Text]
$sel:declaredTransforms:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe [Text]
declaredTransforms} -> Maybe [Text]
declaredTransforms) (\s :: GetTemplateSummaryResponse
s@GetTemplateSummaryResponse' {} Maybe [Text]
a -> GetTemplateSummaryResponse
s {$sel:declaredTransforms:GetTemplateSummaryResponse' :: Maybe [Text]
declaredTransforms = Maybe [Text]
a} :: GetTemplateSummaryResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The value that\'s defined in the @Description@ property of the template.
getTemplateSummaryResponse_description :: Lens.Lens' GetTemplateSummaryResponse (Prelude.Maybe Prelude.Text)
getTemplateSummaryResponse_description :: Lens' GetTemplateSummaryResponse (Maybe Text)
getTemplateSummaryResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummaryResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetTemplateSummaryResponse
s@GetTemplateSummaryResponse' {} Maybe Text
a -> GetTemplateSummaryResponse
s {$sel:description:GetTemplateSummaryResponse' :: Maybe Text
description = Maybe Text
a} :: GetTemplateSummaryResponse)

-- | The value that\'s defined for the @Metadata@ property of the template.
getTemplateSummaryResponse_metadata :: Lens.Lens' GetTemplateSummaryResponse (Prelude.Maybe Prelude.Text)
getTemplateSummaryResponse_metadata :: Lens' GetTemplateSummaryResponse (Maybe Text)
getTemplateSummaryResponse_metadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummaryResponse' {Maybe Text
metadata :: Maybe Text
$sel:metadata:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe Text
metadata} -> Maybe Text
metadata) (\s :: GetTemplateSummaryResponse
s@GetTemplateSummaryResponse' {} Maybe Text
a -> GetTemplateSummaryResponse
s {$sel:metadata:GetTemplateSummaryResponse' :: Maybe Text
metadata = Maybe Text
a} :: GetTemplateSummaryResponse)

-- | A list of parameter declarations that describe various properties for
-- each parameter.
getTemplateSummaryResponse_parameters :: Lens.Lens' GetTemplateSummaryResponse (Prelude.Maybe [ParameterDeclaration])
getTemplateSummaryResponse_parameters :: Lens' GetTemplateSummaryResponse (Maybe [ParameterDeclaration])
getTemplateSummaryResponse_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummaryResponse' {Maybe [ParameterDeclaration]
parameters :: Maybe [ParameterDeclaration]
$sel:parameters:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe [ParameterDeclaration]
parameters} -> Maybe [ParameterDeclaration]
parameters) (\s :: GetTemplateSummaryResponse
s@GetTemplateSummaryResponse' {} Maybe [ParameterDeclaration]
a -> GetTemplateSummaryResponse
s {$sel:parameters:GetTemplateSummaryResponse' :: Maybe [ParameterDeclaration]
parameters = Maybe [ParameterDeclaration]
a} :: GetTemplateSummaryResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A list of resource identifier summaries that describe the target
-- resources of an import operation and the properties you can provide
-- during the import to identify the target resources. For example,
-- @BucketName@ is a possible identifier property for an @AWS::S3::Bucket@
-- resource.
getTemplateSummaryResponse_resourceIdentifierSummaries :: Lens.Lens' GetTemplateSummaryResponse (Prelude.Maybe [ResourceIdentifierSummary])
getTemplateSummaryResponse_resourceIdentifierSummaries :: Lens'
  GetTemplateSummaryResponse (Maybe [ResourceIdentifierSummary])
getTemplateSummaryResponse_resourceIdentifierSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummaryResponse' {Maybe [ResourceIdentifierSummary]
resourceIdentifierSummaries :: Maybe [ResourceIdentifierSummary]
$sel:resourceIdentifierSummaries:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe [ResourceIdentifierSummary]
resourceIdentifierSummaries} -> Maybe [ResourceIdentifierSummary]
resourceIdentifierSummaries) (\s :: GetTemplateSummaryResponse
s@GetTemplateSummaryResponse' {} Maybe [ResourceIdentifierSummary]
a -> GetTemplateSummaryResponse
s {$sel:resourceIdentifierSummaries:GetTemplateSummaryResponse' :: Maybe [ResourceIdentifierSummary]
resourceIdentifierSummaries = Maybe [ResourceIdentifierSummary]
a} :: GetTemplateSummaryResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A list of all the template resource types that are defined in the
-- template, such as @AWS::EC2::Instance@, @AWS::Dynamo::Table@, and
-- @Custom::MyCustomInstance@.
getTemplateSummaryResponse_resourceTypes :: Lens.Lens' GetTemplateSummaryResponse (Prelude.Maybe [Prelude.Text])
getTemplateSummaryResponse_resourceTypes :: Lens' GetTemplateSummaryResponse (Maybe [Text])
getTemplateSummaryResponse_resourceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummaryResponse' {Maybe [Text]
resourceTypes :: Maybe [Text]
$sel:resourceTypes:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe [Text]
resourceTypes} -> Maybe [Text]
resourceTypes) (\s :: GetTemplateSummaryResponse
s@GetTemplateSummaryResponse' {} Maybe [Text]
a -> GetTemplateSummaryResponse
s {$sel:resourceTypes:GetTemplateSummaryResponse' :: Maybe [Text]
resourceTypes = Maybe [Text]
a} :: GetTemplateSummaryResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The Amazon Web Services template format version, which identifies the
-- capabilities of the template.
getTemplateSummaryResponse_version :: Lens.Lens' GetTemplateSummaryResponse (Prelude.Maybe Prelude.Text)
getTemplateSummaryResponse_version :: Lens' GetTemplateSummaryResponse (Maybe Text)
getTemplateSummaryResponse_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateSummaryResponse' {Maybe Text
version :: Maybe Text
$sel:version:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe Text
version} -> Maybe Text
version) (\s :: GetTemplateSummaryResponse
s@GetTemplateSummaryResponse' {} Maybe Text
a -> GetTemplateSummaryResponse
s {$sel:version:GetTemplateSummaryResponse' :: Maybe Text
version = Maybe Text
a} :: GetTemplateSummaryResponse)

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

instance Prelude.NFData GetTemplateSummaryResponse where
  rnf :: GetTemplateSummaryResponse -> ()
rnf GetTemplateSummaryResponse' {Int
Maybe [Text]
Maybe [Capability]
Maybe [ParameterDeclaration]
Maybe [ResourceIdentifierSummary]
Maybe Text
httpStatus :: Int
version :: Maybe Text
resourceTypes :: Maybe [Text]
resourceIdentifierSummaries :: Maybe [ResourceIdentifierSummary]
parameters :: Maybe [ParameterDeclaration]
metadata :: Maybe Text
description :: Maybe Text
declaredTransforms :: Maybe [Text]
capabilitiesReason :: Maybe Text
capabilities :: Maybe [Capability]
$sel:httpStatus:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Int
$sel:version:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe Text
$sel:resourceTypes:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe [Text]
$sel:resourceIdentifierSummaries:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe [ResourceIdentifierSummary]
$sel:parameters:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe [ParameterDeclaration]
$sel:metadata:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe Text
$sel:description:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe Text
$sel:declaredTransforms:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe [Text]
$sel:capabilitiesReason:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe Text
$sel:capabilities:GetTemplateSummaryResponse' :: GetTemplateSummaryResponse -> Maybe [Capability]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Capability]
capabilities
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
capabilitiesReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
declaredTransforms
      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 Text
metadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ParameterDeclaration]
parameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ResourceIdentifierSummary]
resourceIdentifierSummaries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
resourceTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus