{-# 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.AutoScalingPlans.DeleteScalingPlan
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes the specified scaling plan.
--
-- Deleting a scaling plan deletes the underlying ScalingInstruction for
-- all of the scalable resources that are covered by the plan.
--
-- If the plan has launched resources or has scaling activities in
-- progress, you must delete those resources separately.
module Amazonka.AutoScalingPlans.DeleteScalingPlan
  ( -- * Creating a Request
    DeleteScalingPlan (..),
    newDeleteScalingPlan,

    -- * Request Lenses
    deleteScalingPlan_scalingPlanName,
    deleteScalingPlan_scalingPlanVersion,

    -- * Destructuring the Response
    DeleteScalingPlanResponse (..),
    newDeleteScalingPlanResponse,

    -- * Response Lenses
    deleteScalingPlanResponse_httpStatus,
  )
where

import Amazonka.AutoScalingPlans.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:/ 'newDeleteScalingPlan' smart constructor.
data DeleteScalingPlan = DeleteScalingPlan'
  { -- | The name of the scaling plan.
    DeleteScalingPlan -> Text
scalingPlanName :: Prelude.Text,
    -- | The version number of the scaling plan. Currently, the only valid value
    -- is @1@.
    DeleteScalingPlan -> Integer
scalingPlanVersion :: Prelude.Integer
  }
  deriving (DeleteScalingPlan -> DeleteScalingPlan -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteScalingPlan -> DeleteScalingPlan -> Bool
$c/= :: DeleteScalingPlan -> DeleteScalingPlan -> Bool
== :: DeleteScalingPlan -> DeleteScalingPlan -> Bool
$c== :: DeleteScalingPlan -> DeleteScalingPlan -> Bool
Prelude.Eq, ReadPrec [DeleteScalingPlan]
ReadPrec DeleteScalingPlan
Int -> ReadS DeleteScalingPlan
ReadS [DeleteScalingPlan]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteScalingPlan]
$creadListPrec :: ReadPrec [DeleteScalingPlan]
readPrec :: ReadPrec DeleteScalingPlan
$creadPrec :: ReadPrec DeleteScalingPlan
readList :: ReadS [DeleteScalingPlan]
$creadList :: ReadS [DeleteScalingPlan]
readsPrec :: Int -> ReadS DeleteScalingPlan
$creadsPrec :: Int -> ReadS DeleteScalingPlan
Prelude.Read, Int -> DeleteScalingPlan -> ShowS
[DeleteScalingPlan] -> ShowS
DeleteScalingPlan -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteScalingPlan] -> ShowS
$cshowList :: [DeleteScalingPlan] -> ShowS
show :: DeleteScalingPlan -> String
$cshow :: DeleteScalingPlan -> String
showsPrec :: Int -> DeleteScalingPlan -> ShowS
$cshowsPrec :: Int -> DeleteScalingPlan -> ShowS
Prelude.Show, forall x. Rep DeleteScalingPlan x -> DeleteScalingPlan
forall x. DeleteScalingPlan -> Rep DeleteScalingPlan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteScalingPlan x -> DeleteScalingPlan
$cfrom :: forall x. DeleteScalingPlan -> Rep DeleteScalingPlan x
Prelude.Generic)

-- |
-- Create a value of 'DeleteScalingPlan' 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:
--
-- 'scalingPlanName', 'deleteScalingPlan_scalingPlanName' - The name of the scaling plan.
--
-- 'scalingPlanVersion', 'deleteScalingPlan_scalingPlanVersion' - The version number of the scaling plan. Currently, the only valid value
-- is @1@.
newDeleteScalingPlan ::
  -- | 'scalingPlanName'
  Prelude.Text ->
  -- | 'scalingPlanVersion'
  Prelude.Integer ->
  DeleteScalingPlan
newDeleteScalingPlan :: Text -> Integer -> DeleteScalingPlan
newDeleteScalingPlan
  Text
pScalingPlanName_
  Integer
pScalingPlanVersion_ =
    DeleteScalingPlan'
      { $sel:scalingPlanName:DeleteScalingPlan' :: Text
scalingPlanName =
          Text
pScalingPlanName_,
        $sel:scalingPlanVersion:DeleteScalingPlan' :: Integer
scalingPlanVersion = Integer
pScalingPlanVersion_
      }

-- | The name of the scaling plan.
deleteScalingPlan_scalingPlanName :: Lens.Lens' DeleteScalingPlan Prelude.Text
deleteScalingPlan_scalingPlanName :: Lens' DeleteScalingPlan Text
deleteScalingPlan_scalingPlanName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteScalingPlan' {Text
scalingPlanName :: Text
$sel:scalingPlanName:DeleteScalingPlan' :: DeleteScalingPlan -> Text
scalingPlanName} -> Text
scalingPlanName) (\s :: DeleteScalingPlan
s@DeleteScalingPlan' {} Text
a -> DeleteScalingPlan
s {$sel:scalingPlanName:DeleteScalingPlan' :: Text
scalingPlanName = Text
a} :: DeleteScalingPlan)

-- | The version number of the scaling plan. Currently, the only valid value
-- is @1@.
deleteScalingPlan_scalingPlanVersion :: Lens.Lens' DeleteScalingPlan Prelude.Integer
deleteScalingPlan_scalingPlanVersion :: Lens' DeleteScalingPlan Integer
deleteScalingPlan_scalingPlanVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteScalingPlan' {Integer
scalingPlanVersion :: Integer
$sel:scalingPlanVersion:DeleteScalingPlan' :: DeleteScalingPlan -> Integer
scalingPlanVersion} -> Integer
scalingPlanVersion) (\s :: DeleteScalingPlan
s@DeleteScalingPlan' {} Integer
a -> DeleteScalingPlan
s {$sel:scalingPlanVersion:DeleteScalingPlan' :: Integer
scalingPlanVersion = Integer
a} :: DeleteScalingPlan)

instance Core.AWSRequest DeleteScalingPlan where
  type
    AWSResponse DeleteScalingPlan =
      DeleteScalingPlanResponse
  request :: (Service -> Service)
-> DeleteScalingPlan -> Request DeleteScalingPlan
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 DeleteScalingPlan
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteScalingPlan)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteScalingPlanResponse
DeleteScalingPlanResponse'
            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))
      )

instance Prelude.Hashable DeleteScalingPlan where
  hashWithSalt :: Int -> DeleteScalingPlan -> Int
hashWithSalt Int
_salt DeleteScalingPlan' {Integer
Text
scalingPlanVersion :: Integer
scalingPlanName :: Text
$sel:scalingPlanVersion:DeleteScalingPlan' :: DeleteScalingPlan -> Integer
$sel:scalingPlanName:DeleteScalingPlan' :: DeleteScalingPlan -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
scalingPlanName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Integer
scalingPlanVersion

instance Prelude.NFData DeleteScalingPlan where
  rnf :: DeleteScalingPlan -> ()
rnf DeleteScalingPlan' {Integer
Text
scalingPlanVersion :: Integer
scalingPlanName :: Text
$sel:scalingPlanVersion:DeleteScalingPlan' :: DeleteScalingPlan -> Integer
$sel:scalingPlanName:DeleteScalingPlan' :: DeleteScalingPlan -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
scalingPlanName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Integer
scalingPlanVersion

instance Data.ToHeaders DeleteScalingPlan where
  toHeaders :: DeleteScalingPlan -> 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
"AnyScaleScalingPlannerFrontendService.DeleteScalingPlan" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteScalingPlan where
  toJSON :: DeleteScalingPlan -> Value
toJSON DeleteScalingPlan' {Integer
Text
scalingPlanVersion :: Integer
scalingPlanName :: Text
$sel:scalingPlanVersion:DeleteScalingPlan' :: DeleteScalingPlan -> Integer
$sel:scalingPlanName:DeleteScalingPlan' :: DeleteScalingPlan -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"ScalingPlanName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
scalingPlanName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ScalingPlanVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Integer
scalingPlanVersion)
          ]
      )

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

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

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

-- |
-- Create a value of 'DeleteScalingPlanResponse' 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', 'deleteScalingPlanResponse_httpStatus' - The response's http status code.
newDeleteScalingPlanResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteScalingPlanResponse
newDeleteScalingPlanResponse :: Int -> DeleteScalingPlanResponse
newDeleteScalingPlanResponse Int
pHttpStatus_ =
  DeleteScalingPlanResponse'
    { $sel:httpStatus:DeleteScalingPlanResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData DeleteScalingPlanResponse where
  rnf :: DeleteScalingPlanResponse -> ()
rnf DeleteScalingPlanResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteScalingPlanResponse' :: DeleteScalingPlanResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus