{-# 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.UpdateScalingPlan
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the specified scaling plan.
--
-- You cannot update a scaling plan if it is in the process of being
-- created, updated, or deleted.
module Amazonka.AutoScalingPlans.UpdateScalingPlan
  ( -- * Creating a Request
    UpdateScalingPlan (..),
    newUpdateScalingPlan,

    -- * Request Lenses
    updateScalingPlan_applicationSource,
    updateScalingPlan_scalingInstructions,
    updateScalingPlan_scalingPlanName,
    updateScalingPlan_scalingPlanVersion,

    -- * Destructuring the Response
    UpdateScalingPlanResponse (..),
    newUpdateScalingPlanResponse,

    -- * Response Lenses
    updateScalingPlanResponse_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:/ 'newUpdateScalingPlan' smart constructor.
data UpdateScalingPlan = UpdateScalingPlan'
  { -- | A CloudFormation stack or set of tags.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/plans/APIReference/API_ApplicationSource.html ApplicationSource>
    -- in the /AWS Auto Scaling API Reference/.
    UpdateScalingPlan -> Maybe ApplicationSource
applicationSource :: Prelude.Maybe ApplicationSource,
    -- | The scaling instructions.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/plans/APIReference/API_ScalingInstruction.html ScalingInstruction>
    -- in the /AWS Auto Scaling API Reference/.
    UpdateScalingPlan -> Maybe [ScalingInstruction]
scalingInstructions :: Prelude.Maybe [ScalingInstruction],
    -- | The name of the scaling plan.
    UpdateScalingPlan -> Text
scalingPlanName :: Prelude.Text,
    -- | The version number of the scaling plan. The only valid value is @1@.
    -- Currently, you cannot have multiple scaling plan versions.
    UpdateScalingPlan -> Integer
scalingPlanVersion :: Prelude.Integer
  }
  deriving (UpdateScalingPlan -> UpdateScalingPlan -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateScalingPlan -> UpdateScalingPlan -> Bool
$c/= :: UpdateScalingPlan -> UpdateScalingPlan -> Bool
== :: UpdateScalingPlan -> UpdateScalingPlan -> Bool
$c== :: UpdateScalingPlan -> UpdateScalingPlan -> Bool
Prelude.Eq, ReadPrec [UpdateScalingPlan]
ReadPrec UpdateScalingPlan
Int -> ReadS UpdateScalingPlan
ReadS [UpdateScalingPlan]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateScalingPlan]
$creadListPrec :: ReadPrec [UpdateScalingPlan]
readPrec :: ReadPrec UpdateScalingPlan
$creadPrec :: ReadPrec UpdateScalingPlan
readList :: ReadS [UpdateScalingPlan]
$creadList :: ReadS [UpdateScalingPlan]
readsPrec :: Int -> ReadS UpdateScalingPlan
$creadsPrec :: Int -> ReadS UpdateScalingPlan
Prelude.Read, Int -> UpdateScalingPlan -> ShowS
[UpdateScalingPlan] -> ShowS
UpdateScalingPlan -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateScalingPlan] -> ShowS
$cshowList :: [UpdateScalingPlan] -> ShowS
show :: UpdateScalingPlan -> String
$cshow :: UpdateScalingPlan -> String
showsPrec :: Int -> UpdateScalingPlan -> ShowS
$cshowsPrec :: Int -> UpdateScalingPlan -> ShowS
Prelude.Show, forall x. Rep UpdateScalingPlan x -> UpdateScalingPlan
forall x. UpdateScalingPlan -> Rep UpdateScalingPlan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateScalingPlan x -> UpdateScalingPlan
$cfrom :: forall x. UpdateScalingPlan -> Rep UpdateScalingPlan x
Prelude.Generic)

-- |
-- Create a value of 'UpdateScalingPlan' 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:
--
-- 'applicationSource', 'updateScalingPlan_applicationSource' - A CloudFormation stack or set of tags.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/plans/APIReference/API_ApplicationSource.html ApplicationSource>
-- in the /AWS Auto Scaling API Reference/.
--
-- 'scalingInstructions', 'updateScalingPlan_scalingInstructions' - The scaling instructions.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/plans/APIReference/API_ScalingInstruction.html ScalingInstruction>
-- in the /AWS Auto Scaling API Reference/.
--
-- 'scalingPlanName', 'updateScalingPlan_scalingPlanName' - The name of the scaling plan.
--
-- 'scalingPlanVersion', 'updateScalingPlan_scalingPlanVersion' - The version number of the scaling plan. The only valid value is @1@.
-- Currently, you cannot have multiple scaling plan versions.
newUpdateScalingPlan ::
  -- | 'scalingPlanName'
  Prelude.Text ->
  -- | 'scalingPlanVersion'
  Prelude.Integer ->
  UpdateScalingPlan
newUpdateScalingPlan :: Text -> Integer -> UpdateScalingPlan
newUpdateScalingPlan
  Text
pScalingPlanName_
  Integer
pScalingPlanVersion_ =
    UpdateScalingPlan'
      { $sel:applicationSource:UpdateScalingPlan' :: Maybe ApplicationSource
applicationSource =
          forall a. Maybe a
Prelude.Nothing,
        $sel:scalingInstructions:UpdateScalingPlan' :: Maybe [ScalingInstruction]
scalingInstructions = forall a. Maybe a
Prelude.Nothing,
        $sel:scalingPlanName:UpdateScalingPlan' :: Text
scalingPlanName = Text
pScalingPlanName_,
        $sel:scalingPlanVersion:UpdateScalingPlan' :: Integer
scalingPlanVersion = Integer
pScalingPlanVersion_
      }

-- | A CloudFormation stack or set of tags.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/plans/APIReference/API_ApplicationSource.html ApplicationSource>
-- in the /AWS Auto Scaling API Reference/.
updateScalingPlan_applicationSource :: Lens.Lens' UpdateScalingPlan (Prelude.Maybe ApplicationSource)
updateScalingPlan_applicationSource :: Lens' UpdateScalingPlan (Maybe ApplicationSource)
updateScalingPlan_applicationSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateScalingPlan' {Maybe ApplicationSource
applicationSource :: Maybe ApplicationSource
$sel:applicationSource:UpdateScalingPlan' :: UpdateScalingPlan -> Maybe ApplicationSource
applicationSource} -> Maybe ApplicationSource
applicationSource) (\s :: UpdateScalingPlan
s@UpdateScalingPlan' {} Maybe ApplicationSource
a -> UpdateScalingPlan
s {$sel:applicationSource:UpdateScalingPlan' :: Maybe ApplicationSource
applicationSource = Maybe ApplicationSource
a} :: UpdateScalingPlan)

-- | The scaling instructions.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/plans/APIReference/API_ScalingInstruction.html ScalingInstruction>
-- in the /AWS Auto Scaling API Reference/.
updateScalingPlan_scalingInstructions :: Lens.Lens' UpdateScalingPlan (Prelude.Maybe [ScalingInstruction])
updateScalingPlan_scalingInstructions :: Lens' UpdateScalingPlan (Maybe [ScalingInstruction])
updateScalingPlan_scalingInstructions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateScalingPlan' {Maybe [ScalingInstruction]
scalingInstructions :: Maybe [ScalingInstruction]
$sel:scalingInstructions:UpdateScalingPlan' :: UpdateScalingPlan -> Maybe [ScalingInstruction]
scalingInstructions} -> Maybe [ScalingInstruction]
scalingInstructions) (\s :: UpdateScalingPlan
s@UpdateScalingPlan' {} Maybe [ScalingInstruction]
a -> UpdateScalingPlan
s {$sel:scalingInstructions:UpdateScalingPlan' :: Maybe [ScalingInstruction]
scalingInstructions = Maybe [ScalingInstruction]
a} :: UpdateScalingPlan) 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 name of the scaling plan.
updateScalingPlan_scalingPlanName :: Lens.Lens' UpdateScalingPlan Prelude.Text
updateScalingPlan_scalingPlanName :: Lens' UpdateScalingPlan Text
updateScalingPlan_scalingPlanName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateScalingPlan' {Text
scalingPlanName :: Text
$sel:scalingPlanName:UpdateScalingPlan' :: UpdateScalingPlan -> Text
scalingPlanName} -> Text
scalingPlanName) (\s :: UpdateScalingPlan
s@UpdateScalingPlan' {} Text
a -> UpdateScalingPlan
s {$sel:scalingPlanName:UpdateScalingPlan' :: Text
scalingPlanName = Text
a} :: UpdateScalingPlan)

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

instance Core.AWSRequest UpdateScalingPlan where
  type
    AWSResponse UpdateScalingPlan =
      UpdateScalingPlanResponse
  request :: (Service -> Service)
-> UpdateScalingPlan -> Request UpdateScalingPlan
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 UpdateScalingPlan
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateScalingPlan)))
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 -> UpdateScalingPlanResponse
UpdateScalingPlanResponse'
            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 UpdateScalingPlan where
  hashWithSalt :: Int -> UpdateScalingPlan -> Int
hashWithSalt Int
_salt UpdateScalingPlan' {Integer
Maybe [ScalingInstruction]
Maybe ApplicationSource
Text
scalingPlanVersion :: Integer
scalingPlanName :: Text
scalingInstructions :: Maybe [ScalingInstruction]
applicationSource :: Maybe ApplicationSource
$sel:scalingPlanVersion:UpdateScalingPlan' :: UpdateScalingPlan -> Integer
$sel:scalingPlanName:UpdateScalingPlan' :: UpdateScalingPlan -> Text
$sel:scalingInstructions:UpdateScalingPlan' :: UpdateScalingPlan -> Maybe [ScalingInstruction]
$sel:applicationSource:UpdateScalingPlan' :: UpdateScalingPlan -> Maybe ApplicationSource
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ApplicationSource
applicationSource
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ScalingInstruction]
scalingInstructions
      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 UpdateScalingPlan where
  rnf :: UpdateScalingPlan -> ()
rnf UpdateScalingPlan' {Integer
Maybe [ScalingInstruction]
Maybe ApplicationSource
Text
scalingPlanVersion :: Integer
scalingPlanName :: Text
scalingInstructions :: Maybe [ScalingInstruction]
applicationSource :: Maybe ApplicationSource
$sel:scalingPlanVersion:UpdateScalingPlan' :: UpdateScalingPlan -> Integer
$sel:scalingPlanName:UpdateScalingPlan' :: UpdateScalingPlan -> Text
$sel:scalingInstructions:UpdateScalingPlan' :: UpdateScalingPlan -> Maybe [ScalingInstruction]
$sel:applicationSource:UpdateScalingPlan' :: UpdateScalingPlan -> Maybe ApplicationSource
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ApplicationSource
applicationSource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ScalingInstruction]
scalingInstructions
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 UpdateScalingPlan where
  toHeaders :: UpdateScalingPlan -> 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.UpdateScalingPlan" ::
                          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 UpdateScalingPlan where
  toJSON :: UpdateScalingPlan -> Value
toJSON UpdateScalingPlan' {Integer
Maybe [ScalingInstruction]
Maybe ApplicationSource
Text
scalingPlanVersion :: Integer
scalingPlanName :: Text
scalingInstructions :: Maybe [ScalingInstruction]
applicationSource :: Maybe ApplicationSource
$sel:scalingPlanVersion:UpdateScalingPlan' :: UpdateScalingPlan -> Integer
$sel:scalingPlanName:UpdateScalingPlan' :: UpdateScalingPlan -> Text
$sel:scalingInstructions:UpdateScalingPlan' :: UpdateScalingPlan -> Maybe [ScalingInstruction]
$sel:applicationSource:UpdateScalingPlan' :: UpdateScalingPlan -> Maybe ApplicationSource
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ApplicationSource" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ApplicationSource
applicationSource,
            (Key
"ScalingInstructions" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ScalingInstruction]
scalingInstructions,
            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 UpdateScalingPlan where
  toPath :: UpdateScalingPlan -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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