{-# 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.Proton.DeleteEnvironmentTemplateVersion
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- If no other minor versions of an environment template exist, delete a
-- major version of the environment template if it\'s not the @Recommended@
-- version. Delete the @Recommended@ version of the environment template if
-- no other major versions or minor versions of the environment template
-- exist. A major version of an environment template is a version that\'s
-- not backward compatible.
--
-- Delete a minor version of an environment template if it /isn\'t/ the
-- @Recommended@ version. Delete a @Recommended@ minor version of the
-- environment template if no other minor versions of the environment
-- template exist. A minor version of an environment template is a version
-- that\'s backward compatible.
module Amazonka.Proton.DeleteEnvironmentTemplateVersion
  ( -- * Creating a Request
    DeleteEnvironmentTemplateVersion (..),
    newDeleteEnvironmentTemplateVersion,

    -- * Request Lenses
    deleteEnvironmentTemplateVersion_majorVersion,
    deleteEnvironmentTemplateVersion_minorVersion,
    deleteEnvironmentTemplateVersion_templateName,

    -- * Destructuring the Response
    DeleteEnvironmentTemplateVersionResponse (..),
    newDeleteEnvironmentTemplateVersionResponse,

    -- * Response Lenses
    deleteEnvironmentTemplateVersionResponse_environmentTemplateVersion,
    deleteEnvironmentTemplateVersionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteEnvironmentTemplateVersion' smart constructor.
data DeleteEnvironmentTemplateVersion = DeleteEnvironmentTemplateVersion'
  { -- | The environment template major version to delete.
    DeleteEnvironmentTemplateVersion -> Text
majorVersion :: Prelude.Text,
    -- | The environment template minor version to delete.
    DeleteEnvironmentTemplateVersion -> Text
minorVersion :: Prelude.Text,
    -- | The name of the environment template.
    DeleteEnvironmentTemplateVersion -> Text
templateName :: Prelude.Text
  }
  deriving (DeleteEnvironmentTemplateVersion
-> DeleteEnvironmentTemplateVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteEnvironmentTemplateVersion
-> DeleteEnvironmentTemplateVersion -> Bool
$c/= :: DeleteEnvironmentTemplateVersion
-> DeleteEnvironmentTemplateVersion -> Bool
== :: DeleteEnvironmentTemplateVersion
-> DeleteEnvironmentTemplateVersion -> Bool
$c== :: DeleteEnvironmentTemplateVersion
-> DeleteEnvironmentTemplateVersion -> Bool
Prelude.Eq, ReadPrec [DeleteEnvironmentTemplateVersion]
ReadPrec DeleteEnvironmentTemplateVersion
Int -> ReadS DeleteEnvironmentTemplateVersion
ReadS [DeleteEnvironmentTemplateVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteEnvironmentTemplateVersion]
$creadListPrec :: ReadPrec [DeleteEnvironmentTemplateVersion]
readPrec :: ReadPrec DeleteEnvironmentTemplateVersion
$creadPrec :: ReadPrec DeleteEnvironmentTemplateVersion
readList :: ReadS [DeleteEnvironmentTemplateVersion]
$creadList :: ReadS [DeleteEnvironmentTemplateVersion]
readsPrec :: Int -> ReadS DeleteEnvironmentTemplateVersion
$creadsPrec :: Int -> ReadS DeleteEnvironmentTemplateVersion
Prelude.Read, Int -> DeleteEnvironmentTemplateVersion -> ShowS
[DeleteEnvironmentTemplateVersion] -> ShowS
DeleteEnvironmentTemplateVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteEnvironmentTemplateVersion] -> ShowS
$cshowList :: [DeleteEnvironmentTemplateVersion] -> ShowS
show :: DeleteEnvironmentTemplateVersion -> String
$cshow :: DeleteEnvironmentTemplateVersion -> String
showsPrec :: Int -> DeleteEnvironmentTemplateVersion -> ShowS
$cshowsPrec :: Int -> DeleteEnvironmentTemplateVersion -> ShowS
Prelude.Show, forall x.
Rep DeleteEnvironmentTemplateVersion x
-> DeleteEnvironmentTemplateVersion
forall x.
DeleteEnvironmentTemplateVersion
-> Rep DeleteEnvironmentTemplateVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteEnvironmentTemplateVersion x
-> DeleteEnvironmentTemplateVersion
$cfrom :: forall x.
DeleteEnvironmentTemplateVersion
-> Rep DeleteEnvironmentTemplateVersion x
Prelude.Generic)

-- |
-- Create a value of 'DeleteEnvironmentTemplateVersion' 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:
--
-- 'majorVersion', 'deleteEnvironmentTemplateVersion_majorVersion' - The environment template major version to delete.
--
-- 'minorVersion', 'deleteEnvironmentTemplateVersion_minorVersion' - The environment template minor version to delete.
--
-- 'templateName', 'deleteEnvironmentTemplateVersion_templateName' - The name of the environment template.
newDeleteEnvironmentTemplateVersion ::
  -- | 'majorVersion'
  Prelude.Text ->
  -- | 'minorVersion'
  Prelude.Text ->
  -- | 'templateName'
  Prelude.Text ->
  DeleteEnvironmentTemplateVersion
newDeleteEnvironmentTemplateVersion :: Text -> Text -> Text -> DeleteEnvironmentTemplateVersion
newDeleteEnvironmentTemplateVersion
  Text
pMajorVersion_
  Text
pMinorVersion_
  Text
pTemplateName_ =
    DeleteEnvironmentTemplateVersion'
      { $sel:majorVersion:DeleteEnvironmentTemplateVersion' :: Text
majorVersion =
          Text
pMajorVersion_,
        $sel:minorVersion:DeleteEnvironmentTemplateVersion' :: Text
minorVersion = Text
pMinorVersion_,
        $sel:templateName:DeleteEnvironmentTemplateVersion' :: Text
templateName = Text
pTemplateName_
      }

-- | The environment template major version to delete.
deleteEnvironmentTemplateVersion_majorVersion :: Lens.Lens' DeleteEnvironmentTemplateVersion Prelude.Text
deleteEnvironmentTemplateVersion_majorVersion :: Lens' DeleteEnvironmentTemplateVersion Text
deleteEnvironmentTemplateVersion_majorVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEnvironmentTemplateVersion' {Text
majorVersion :: Text
$sel:majorVersion:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
majorVersion} -> Text
majorVersion) (\s :: DeleteEnvironmentTemplateVersion
s@DeleteEnvironmentTemplateVersion' {} Text
a -> DeleteEnvironmentTemplateVersion
s {$sel:majorVersion:DeleteEnvironmentTemplateVersion' :: Text
majorVersion = Text
a} :: DeleteEnvironmentTemplateVersion)

-- | The environment template minor version to delete.
deleteEnvironmentTemplateVersion_minorVersion :: Lens.Lens' DeleteEnvironmentTemplateVersion Prelude.Text
deleteEnvironmentTemplateVersion_minorVersion :: Lens' DeleteEnvironmentTemplateVersion Text
deleteEnvironmentTemplateVersion_minorVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEnvironmentTemplateVersion' {Text
minorVersion :: Text
$sel:minorVersion:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
minorVersion} -> Text
minorVersion) (\s :: DeleteEnvironmentTemplateVersion
s@DeleteEnvironmentTemplateVersion' {} Text
a -> DeleteEnvironmentTemplateVersion
s {$sel:minorVersion:DeleteEnvironmentTemplateVersion' :: Text
minorVersion = Text
a} :: DeleteEnvironmentTemplateVersion)

-- | The name of the environment template.
deleteEnvironmentTemplateVersion_templateName :: Lens.Lens' DeleteEnvironmentTemplateVersion Prelude.Text
deleteEnvironmentTemplateVersion_templateName :: Lens' DeleteEnvironmentTemplateVersion Text
deleteEnvironmentTemplateVersion_templateName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEnvironmentTemplateVersion' {Text
templateName :: Text
$sel:templateName:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
templateName} -> Text
templateName) (\s :: DeleteEnvironmentTemplateVersion
s@DeleteEnvironmentTemplateVersion' {} Text
a -> DeleteEnvironmentTemplateVersion
s {$sel:templateName:DeleteEnvironmentTemplateVersion' :: Text
templateName = Text
a} :: DeleteEnvironmentTemplateVersion)

instance
  Core.AWSRequest
    DeleteEnvironmentTemplateVersion
  where
  type
    AWSResponse DeleteEnvironmentTemplateVersion =
      DeleteEnvironmentTemplateVersionResponse
  request :: (Service -> Service)
-> DeleteEnvironmentTemplateVersion
-> Request DeleteEnvironmentTemplateVersion
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteEnvironmentTemplateVersion
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DeleteEnvironmentTemplateVersion)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe EnvironmentTemplateVersion
-> Int -> DeleteEnvironmentTemplateVersionResponse
DeleteEnvironmentTemplateVersionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"environmentTemplateVersion")
            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
    DeleteEnvironmentTemplateVersion
  where
  hashWithSalt :: Int -> DeleteEnvironmentTemplateVersion -> Int
hashWithSalt
    Int
_salt
    DeleteEnvironmentTemplateVersion' {Text
templateName :: Text
minorVersion :: Text
majorVersion :: Text
$sel:templateName:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
$sel:minorVersion:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
$sel:majorVersion:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
majorVersion
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
minorVersion
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
templateName

instance
  Prelude.NFData
    DeleteEnvironmentTemplateVersion
  where
  rnf :: DeleteEnvironmentTemplateVersion -> ()
rnf DeleteEnvironmentTemplateVersion' {Text
templateName :: Text
minorVersion :: Text
majorVersion :: Text
$sel:templateName:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
$sel:minorVersion:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
$sel:majorVersion:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
majorVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
minorVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
templateName

instance
  Data.ToHeaders
    DeleteEnvironmentTemplateVersion
  where
  toHeaders :: DeleteEnvironmentTemplateVersion -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AwsProton20200720.DeleteEnvironmentTemplateVersion" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteEnvironmentTemplateVersion where
  toJSON :: DeleteEnvironmentTemplateVersion -> Value
toJSON DeleteEnvironmentTemplateVersion' {Text
templateName :: Text
minorVersion :: Text
majorVersion :: Text
$sel:templateName:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
$sel:minorVersion:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
$sel:majorVersion:DeleteEnvironmentTemplateVersion' :: DeleteEnvironmentTemplateVersion -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"majorVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
majorVersion),
            forall a. a -> Maybe a
Prelude.Just (Key
"minorVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
minorVersion),
            forall a. a -> Maybe a
Prelude.Just (Key
"templateName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
templateName)
          ]
      )

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

instance
  Data.ToQuery
    DeleteEnvironmentTemplateVersion
  where
  toQuery :: DeleteEnvironmentTemplateVersion -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDeleteEnvironmentTemplateVersionResponse' smart constructor.
data DeleteEnvironmentTemplateVersionResponse = DeleteEnvironmentTemplateVersionResponse'
  { -- | The detailed data of the environment template version being deleted.
    DeleteEnvironmentTemplateVersionResponse
-> Maybe EnvironmentTemplateVersion
environmentTemplateVersion :: Prelude.Maybe EnvironmentTemplateVersion,
    -- | The response's http status code.
    DeleteEnvironmentTemplateVersionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteEnvironmentTemplateVersionResponse
-> DeleteEnvironmentTemplateVersionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteEnvironmentTemplateVersionResponse
-> DeleteEnvironmentTemplateVersionResponse -> Bool
$c/= :: DeleteEnvironmentTemplateVersionResponse
-> DeleteEnvironmentTemplateVersionResponse -> Bool
== :: DeleteEnvironmentTemplateVersionResponse
-> DeleteEnvironmentTemplateVersionResponse -> Bool
$c== :: DeleteEnvironmentTemplateVersionResponse
-> DeleteEnvironmentTemplateVersionResponse -> Bool
Prelude.Eq, Int -> DeleteEnvironmentTemplateVersionResponse -> ShowS
[DeleteEnvironmentTemplateVersionResponse] -> ShowS
DeleteEnvironmentTemplateVersionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteEnvironmentTemplateVersionResponse] -> ShowS
$cshowList :: [DeleteEnvironmentTemplateVersionResponse] -> ShowS
show :: DeleteEnvironmentTemplateVersionResponse -> String
$cshow :: DeleteEnvironmentTemplateVersionResponse -> String
showsPrec :: Int -> DeleteEnvironmentTemplateVersionResponse -> ShowS
$cshowsPrec :: Int -> DeleteEnvironmentTemplateVersionResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteEnvironmentTemplateVersionResponse x
-> DeleteEnvironmentTemplateVersionResponse
forall x.
DeleteEnvironmentTemplateVersionResponse
-> Rep DeleteEnvironmentTemplateVersionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteEnvironmentTemplateVersionResponse x
-> DeleteEnvironmentTemplateVersionResponse
$cfrom :: forall x.
DeleteEnvironmentTemplateVersionResponse
-> Rep DeleteEnvironmentTemplateVersionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteEnvironmentTemplateVersionResponse' 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:
--
-- 'environmentTemplateVersion', 'deleteEnvironmentTemplateVersionResponse_environmentTemplateVersion' - The detailed data of the environment template version being deleted.
--
-- 'httpStatus', 'deleteEnvironmentTemplateVersionResponse_httpStatus' - The response's http status code.
newDeleteEnvironmentTemplateVersionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteEnvironmentTemplateVersionResponse
newDeleteEnvironmentTemplateVersionResponse :: Int -> DeleteEnvironmentTemplateVersionResponse
newDeleteEnvironmentTemplateVersionResponse
  Int
pHttpStatus_ =
    DeleteEnvironmentTemplateVersionResponse'
      { $sel:environmentTemplateVersion:DeleteEnvironmentTemplateVersionResponse' :: Maybe EnvironmentTemplateVersion
environmentTemplateVersion =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DeleteEnvironmentTemplateVersionResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The detailed data of the environment template version being deleted.
deleteEnvironmentTemplateVersionResponse_environmentTemplateVersion :: Lens.Lens' DeleteEnvironmentTemplateVersionResponse (Prelude.Maybe EnvironmentTemplateVersion)
deleteEnvironmentTemplateVersionResponse_environmentTemplateVersion :: Lens'
  DeleteEnvironmentTemplateVersionResponse
  (Maybe EnvironmentTemplateVersion)
deleteEnvironmentTemplateVersionResponse_environmentTemplateVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEnvironmentTemplateVersionResponse' {Maybe EnvironmentTemplateVersion
environmentTemplateVersion :: Maybe EnvironmentTemplateVersion
$sel:environmentTemplateVersion:DeleteEnvironmentTemplateVersionResponse' :: DeleteEnvironmentTemplateVersionResponse
-> Maybe EnvironmentTemplateVersion
environmentTemplateVersion} -> Maybe EnvironmentTemplateVersion
environmentTemplateVersion) (\s :: DeleteEnvironmentTemplateVersionResponse
s@DeleteEnvironmentTemplateVersionResponse' {} Maybe EnvironmentTemplateVersion
a -> DeleteEnvironmentTemplateVersionResponse
s {$sel:environmentTemplateVersion:DeleteEnvironmentTemplateVersionResponse' :: Maybe EnvironmentTemplateVersion
environmentTemplateVersion = Maybe EnvironmentTemplateVersion
a} :: DeleteEnvironmentTemplateVersionResponse)

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

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