{-# 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.AppRunner.DeleteAutoScalingConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Delete an App Runner automatic scaling configuration resource. You can
-- delete a specific revision or the latest active revision. You can\'t
-- delete a configuration that\'s used by one or more App Runner services.
module Amazonka.AppRunner.DeleteAutoScalingConfiguration
  ( -- * Creating a Request
    DeleteAutoScalingConfiguration (..),
    newDeleteAutoScalingConfiguration,

    -- * Request Lenses
    deleteAutoScalingConfiguration_autoScalingConfigurationArn,

    -- * Destructuring the Response
    DeleteAutoScalingConfigurationResponse (..),
    newDeleteAutoScalingConfigurationResponse,

    -- * Response Lenses
    deleteAutoScalingConfigurationResponse_httpStatus,
    deleteAutoScalingConfigurationResponse_autoScalingConfiguration,
  )
where

import Amazonka.AppRunner.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:/ 'newDeleteAutoScalingConfiguration' smart constructor.
data DeleteAutoScalingConfiguration = DeleteAutoScalingConfiguration'
  { -- | The Amazon Resource Name (ARN) of the App Runner auto scaling
    -- configuration that you want to delete.
    --
    -- The ARN can be a full auto scaling configuration ARN, or a partial ARN
    -- ending with either @...\/@/@name@/@ @ or
    -- @...\/@/@name@/@\/@/@revision@/@ @. If a revision isn\'t specified, the
    -- latest active revision is deleted.
    DeleteAutoScalingConfiguration -> Text
autoScalingConfigurationArn :: Prelude.Text
  }
  deriving (DeleteAutoScalingConfiguration
-> DeleteAutoScalingConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAutoScalingConfiguration
-> DeleteAutoScalingConfiguration -> Bool
$c/= :: DeleteAutoScalingConfiguration
-> DeleteAutoScalingConfiguration -> Bool
== :: DeleteAutoScalingConfiguration
-> DeleteAutoScalingConfiguration -> Bool
$c== :: DeleteAutoScalingConfiguration
-> DeleteAutoScalingConfiguration -> Bool
Prelude.Eq, ReadPrec [DeleteAutoScalingConfiguration]
ReadPrec DeleteAutoScalingConfiguration
Int -> ReadS DeleteAutoScalingConfiguration
ReadS [DeleteAutoScalingConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAutoScalingConfiguration]
$creadListPrec :: ReadPrec [DeleteAutoScalingConfiguration]
readPrec :: ReadPrec DeleteAutoScalingConfiguration
$creadPrec :: ReadPrec DeleteAutoScalingConfiguration
readList :: ReadS [DeleteAutoScalingConfiguration]
$creadList :: ReadS [DeleteAutoScalingConfiguration]
readsPrec :: Int -> ReadS DeleteAutoScalingConfiguration
$creadsPrec :: Int -> ReadS DeleteAutoScalingConfiguration
Prelude.Read, Int -> DeleteAutoScalingConfiguration -> ShowS
[DeleteAutoScalingConfiguration] -> ShowS
DeleteAutoScalingConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAutoScalingConfiguration] -> ShowS
$cshowList :: [DeleteAutoScalingConfiguration] -> ShowS
show :: DeleteAutoScalingConfiguration -> String
$cshow :: DeleteAutoScalingConfiguration -> String
showsPrec :: Int -> DeleteAutoScalingConfiguration -> ShowS
$cshowsPrec :: Int -> DeleteAutoScalingConfiguration -> ShowS
Prelude.Show, forall x.
Rep DeleteAutoScalingConfiguration x
-> DeleteAutoScalingConfiguration
forall x.
DeleteAutoScalingConfiguration
-> Rep DeleteAutoScalingConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteAutoScalingConfiguration x
-> DeleteAutoScalingConfiguration
$cfrom :: forall x.
DeleteAutoScalingConfiguration
-> Rep DeleteAutoScalingConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAutoScalingConfiguration' 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:
--
-- 'autoScalingConfigurationArn', 'deleteAutoScalingConfiguration_autoScalingConfigurationArn' - The Amazon Resource Name (ARN) of the App Runner auto scaling
-- configuration that you want to delete.
--
-- The ARN can be a full auto scaling configuration ARN, or a partial ARN
-- ending with either @...\/@/@name@/@ @ or
-- @...\/@/@name@/@\/@/@revision@/@ @. If a revision isn\'t specified, the
-- latest active revision is deleted.
newDeleteAutoScalingConfiguration ::
  -- | 'autoScalingConfigurationArn'
  Prelude.Text ->
  DeleteAutoScalingConfiguration
newDeleteAutoScalingConfiguration :: Text -> DeleteAutoScalingConfiguration
newDeleteAutoScalingConfiguration
  Text
pAutoScalingConfigurationArn_ =
    DeleteAutoScalingConfiguration'
      { $sel:autoScalingConfigurationArn:DeleteAutoScalingConfiguration' :: Text
autoScalingConfigurationArn =
          Text
pAutoScalingConfigurationArn_
      }

-- | The Amazon Resource Name (ARN) of the App Runner auto scaling
-- configuration that you want to delete.
--
-- The ARN can be a full auto scaling configuration ARN, or a partial ARN
-- ending with either @...\/@/@name@/@ @ or
-- @...\/@/@name@/@\/@/@revision@/@ @. If a revision isn\'t specified, the
-- latest active revision is deleted.
deleteAutoScalingConfiguration_autoScalingConfigurationArn :: Lens.Lens' DeleteAutoScalingConfiguration Prelude.Text
deleteAutoScalingConfiguration_autoScalingConfigurationArn :: Lens' DeleteAutoScalingConfiguration Text
deleteAutoScalingConfiguration_autoScalingConfigurationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAutoScalingConfiguration' {Text
autoScalingConfigurationArn :: Text
$sel:autoScalingConfigurationArn:DeleteAutoScalingConfiguration' :: DeleteAutoScalingConfiguration -> Text
autoScalingConfigurationArn} -> Text
autoScalingConfigurationArn) (\s :: DeleteAutoScalingConfiguration
s@DeleteAutoScalingConfiguration' {} Text
a -> DeleteAutoScalingConfiguration
s {$sel:autoScalingConfigurationArn:DeleteAutoScalingConfiguration' :: Text
autoScalingConfigurationArn = Text
a} :: DeleteAutoScalingConfiguration)

instance
  Core.AWSRequest
    DeleteAutoScalingConfiguration
  where
  type
    AWSResponse DeleteAutoScalingConfiguration =
      DeleteAutoScalingConfigurationResponse
  request :: (Service -> Service)
-> DeleteAutoScalingConfiguration
-> Request DeleteAutoScalingConfiguration
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 DeleteAutoScalingConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DeleteAutoScalingConfiguration)))
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 ->
          Int
-> AutoScalingConfiguration
-> DeleteAutoScalingConfigurationResponse
DeleteAutoScalingConfigurationResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"AutoScalingConfiguration")
      )

instance
  Prelude.Hashable
    DeleteAutoScalingConfiguration
  where
  hashWithSalt :: Int -> DeleteAutoScalingConfiguration -> Int
hashWithSalt
    Int
_salt
    DeleteAutoScalingConfiguration' {Text
autoScalingConfigurationArn :: Text
$sel:autoScalingConfigurationArn:DeleteAutoScalingConfiguration' :: DeleteAutoScalingConfiguration -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingConfigurationArn

instance
  Prelude.NFData
    DeleteAutoScalingConfiguration
  where
  rnf :: DeleteAutoScalingConfiguration -> ()
rnf DeleteAutoScalingConfiguration' {Text
autoScalingConfigurationArn :: Text
$sel:autoScalingConfigurationArn:DeleteAutoScalingConfiguration' :: DeleteAutoScalingConfiguration -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
autoScalingConfigurationArn

instance
  Data.ToHeaders
    DeleteAutoScalingConfiguration
  where
  toHeaders :: DeleteAutoScalingConfiguration -> 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
"AppRunner.DeleteAutoScalingConfiguration" ::
                          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 DeleteAutoScalingConfiguration where
  toJSON :: DeleteAutoScalingConfiguration -> Value
toJSON DeleteAutoScalingConfiguration' {Text
autoScalingConfigurationArn :: Text
$sel:autoScalingConfigurationArn:DeleteAutoScalingConfiguration' :: DeleteAutoScalingConfiguration -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"AutoScalingConfigurationArn"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
autoScalingConfigurationArn
              )
          ]
      )

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

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

-- | /See:/ 'newDeleteAutoScalingConfigurationResponse' smart constructor.
data DeleteAutoScalingConfigurationResponse = DeleteAutoScalingConfigurationResponse'
  { -- | The response's http status code.
    DeleteAutoScalingConfigurationResponse -> Int
httpStatus :: Prelude.Int,
    -- | A description of the App Runner auto scaling configuration that this
    -- request just deleted.
    DeleteAutoScalingConfigurationResponse -> AutoScalingConfiguration
autoScalingConfiguration :: AutoScalingConfiguration
  }
  deriving (DeleteAutoScalingConfigurationResponse
-> DeleteAutoScalingConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAutoScalingConfigurationResponse
-> DeleteAutoScalingConfigurationResponse -> Bool
$c/= :: DeleteAutoScalingConfigurationResponse
-> DeleteAutoScalingConfigurationResponse -> Bool
== :: DeleteAutoScalingConfigurationResponse
-> DeleteAutoScalingConfigurationResponse -> Bool
$c== :: DeleteAutoScalingConfigurationResponse
-> DeleteAutoScalingConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [DeleteAutoScalingConfigurationResponse]
ReadPrec DeleteAutoScalingConfigurationResponse
Int -> ReadS DeleteAutoScalingConfigurationResponse
ReadS [DeleteAutoScalingConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAutoScalingConfigurationResponse]
$creadListPrec :: ReadPrec [DeleteAutoScalingConfigurationResponse]
readPrec :: ReadPrec DeleteAutoScalingConfigurationResponse
$creadPrec :: ReadPrec DeleteAutoScalingConfigurationResponse
readList :: ReadS [DeleteAutoScalingConfigurationResponse]
$creadList :: ReadS [DeleteAutoScalingConfigurationResponse]
readsPrec :: Int -> ReadS DeleteAutoScalingConfigurationResponse
$creadsPrec :: Int -> ReadS DeleteAutoScalingConfigurationResponse
Prelude.Read, Int -> DeleteAutoScalingConfigurationResponse -> ShowS
[DeleteAutoScalingConfigurationResponse] -> ShowS
DeleteAutoScalingConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAutoScalingConfigurationResponse] -> ShowS
$cshowList :: [DeleteAutoScalingConfigurationResponse] -> ShowS
show :: DeleteAutoScalingConfigurationResponse -> String
$cshow :: DeleteAutoScalingConfigurationResponse -> String
showsPrec :: Int -> DeleteAutoScalingConfigurationResponse -> ShowS
$cshowsPrec :: Int -> DeleteAutoScalingConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteAutoScalingConfigurationResponse x
-> DeleteAutoScalingConfigurationResponse
forall x.
DeleteAutoScalingConfigurationResponse
-> Rep DeleteAutoScalingConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteAutoScalingConfigurationResponse x
-> DeleteAutoScalingConfigurationResponse
$cfrom :: forall x.
DeleteAutoScalingConfigurationResponse
-> Rep DeleteAutoScalingConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAutoScalingConfigurationResponse' 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:
--
-- 'httpStatus', 'deleteAutoScalingConfigurationResponse_httpStatus' - The response's http status code.
--
-- 'autoScalingConfiguration', 'deleteAutoScalingConfigurationResponse_autoScalingConfiguration' - A description of the App Runner auto scaling configuration that this
-- request just deleted.
newDeleteAutoScalingConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'autoScalingConfiguration'
  AutoScalingConfiguration ->
  DeleteAutoScalingConfigurationResponse
newDeleteAutoScalingConfigurationResponse :: Int
-> AutoScalingConfiguration
-> DeleteAutoScalingConfigurationResponse
newDeleteAutoScalingConfigurationResponse
  Int
pHttpStatus_
  AutoScalingConfiguration
pAutoScalingConfiguration_ =
    DeleteAutoScalingConfigurationResponse'
      { $sel:httpStatus:DeleteAutoScalingConfigurationResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:autoScalingConfiguration:DeleteAutoScalingConfigurationResponse' :: AutoScalingConfiguration
autoScalingConfiguration =
          AutoScalingConfiguration
pAutoScalingConfiguration_
      }

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

-- | A description of the App Runner auto scaling configuration that this
-- request just deleted.
deleteAutoScalingConfigurationResponse_autoScalingConfiguration :: Lens.Lens' DeleteAutoScalingConfigurationResponse AutoScalingConfiguration
deleteAutoScalingConfigurationResponse_autoScalingConfiguration :: Lens'
  DeleteAutoScalingConfigurationResponse AutoScalingConfiguration
deleteAutoScalingConfigurationResponse_autoScalingConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAutoScalingConfigurationResponse' {AutoScalingConfiguration
autoScalingConfiguration :: AutoScalingConfiguration
$sel:autoScalingConfiguration:DeleteAutoScalingConfigurationResponse' :: DeleteAutoScalingConfigurationResponse -> AutoScalingConfiguration
autoScalingConfiguration} -> AutoScalingConfiguration
autoScalingConfiguration) (\s :: DeleteAutoScalingConfigurationResponse
s@DeleteAutoScalingConfigurationResponse' {} AutoScalingConfiguration
a -> DeleteAutoScalingConfigurationResponse
s {$sel:autoScalingConfiguration:DeleteAutoScalingConfigurationResponse' :: AutoScalingConfiguration
autoScalingConfiguration = AutoScalingConfiguration
a} :: DeleteAutoScalingConfigurationResponse)

instance
  Prelude.NFData
    DeleteAutoScalingConfigurationResponse
  where
  rnf :: DeleteAutoScalingConfigurationResponse -> ()
rnf DeleteAutoScalingConfigurationResponse' {Int
AutoScalingConfiguration
autoScalingConfiguration :: AutoScalingConfiguration
httpStatus :: Int
$sel:autoScalingConfiguration:DeleteAutoScalingConfigurationResponse' :: DeleteAutoScalingConfigurationResponse -> AutoScalingConfiguration
$sel:httpStatus:DeleteAutoScalingConfigurationResponse' :: DeleteAutoScalingConfigurationResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AutoScalingConfiguration
autoScalingConfiguration