{-# 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.ApplicationAutoScaling.RegisterScalableTarget
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Registers or updates a scalable target, the resource that you want to
-- scale.
--
-- Scalable targets are uniquely identified by the combination of resource
-- ID, scalable dimension, and namespace, which represents some capacity
-- dimension of the underlying service.
--
-- When you register a new scalable target, you must specify values for the
-- minimum and maximum capacity. If the specified resource is not active in
-- the target service, this operation does not change the resource\'s
-- current capacity. Otherwise, it changes the resource\'s current capacity
-- to a value that is inside of this range.
--
-- If you choose to add a scaling policy, current capacity is adjustable
-- within the specified range when scaling starts. Application Auto Scaling
-- scaling policies will not scale capacity to values that are outside of
-- the minimum and maximum range.
--
-- After you register a scalable target, you do not need to register it
-- again to use other Application Auto Scaling operations. To see which
-- resources have been registered, use
-- <https://docs.aws.amazon.com/autoscaling/application/APIReference/API_DescribeScalableTargets.html DescribeScalableTargets>.
-- You can also view the scaling policies for a service namespace by using
-- <https://docs.aws.amazon.com/autoscaling/application/APIReference/API_DescribeScalableTargets.html DescribeScalableTargets>.
-- If you no longer need a scalable target, you can deregister it by using
-- <https://docs.aws.amazon.com/autoscaling/application/APIReference/API_DeregisterScalableTarget.html DeregisterScalableTarget>.
--
-- To update a scalable target, specify the parameters that you want to
-- change. Include the parameters that identify the scalable target:
-- resource ID, scalable dimension, and namespace. Any parameters that you
-- don\'t specify are not changed by this update request.
--
-- If you call the @RegisterScalableTarget@ API to update an existing
-- scalable target, Application Auto Scaling retrieves the current capacity
-- of the resource. If it is below the minimum capacity or above the
-- maximum capacity, Application Auto Scaling adjusts the capacity of the
-- scalable target to place it within these bounds, even if you don\'t
-- include the @MinCapacity@ or @MaxCapacity@ request parameters.
module Amazonka.ApplicationAutoScaling.RegisterScalableTarget
  ( -- * Creating a Request
    RegisterScalableTarget (..),
    newRegisterScalableTarget,

    -- * Request Lenses
    registerScalableTarget_maxCapacity,
    registerScalableTarget_minCapacity,
    registerScalableTarget_roleARN,
    registerScalableTarget_suspendedState,
    registerScalableTarget_serviceNamespace,
    registerScalableTarget_resourceId,
    registerScalableTarget_scalableDimension,

    -- * Destructuring the Response
    RegisterScalableTargetResponse (..),
    newRegisterScalableTargetResponse,

    -- * Response Lenses
    registerScalableTargetResponse_httpStatus,
  )
where

import Amazonka.ApplicationAutoScaling.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:/ 'newRegisterScalableTarget' smart constructor.
data RegisterScalableTarget = RegisterScalableTarget'
  { -- | The maximum value that you plan to scale out to. When a scaling policy
    -- is in effect, Application Auto Scaling can scale out (expand) as needed
    -- to the maximum capacity limit in response to changing demand. This
    -- property is required when registering a new scalable target.
    --
    -- Although you can specify a large maximum capacity, note that service
    -- quotas may impose lower limits. Each service has its own default quotas
    -- for the maximum capacity of the resource. If you want to specify a
    -- higher limit, you can request an increase. For more information, consult
    -- the documentation for that service. For information about the default
    -- quotas for each service, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-service-information.html Service endpoints and quotas>
    -- in the /Amazon Web Services General Reference/.
    RegisterScalableTarget -> Maybe Int
maxCapacity :: Prelude.Maybe Prelude.Int,
    -- | The minimum value that you plan to scale in to. When a scaling policy is
    -- in effect, Application Auto Scaling can scale in (contract) as needed to
    -- the minimum capacity limit in response to changing demand. This property
    -- is required when registering a new scalable target.
    --
    -- For the following resources, the minimum value allowed is 0.
    --
    -- -   AppStream 2.0 fleets
    --
    -- -   Aurora DB clusters
    --
    -- -   ECS services
    --
    -- -   EMR clusters
    --
    -- -   Lambda provisioned concurrency
    --
    -- -   SageMaker endpoint variants
    --
    -- -   Spot Fleets
    --
    -- -   custom resources
    --
    -- It\'s strongly recommended that you specify a value greater than 0. A
    -- value greater than 0 means that data points are continuously reported to
    -- CloudWatch that scaling policies can use to scale on a metric like
    -- average CPU utilization.
    --
    -- For all other resources, the minimum allowed value depends on the type
    -- of resource that you are using. If you provide a value that is lower
    -- than what a resource can accept, an error occurs. In which case, the
    -- error message will provide the minimum value that the resource can
    -- accept.
    RegisterScalableTarget -> Maybe Int
minCapacity :: Prelude.Maybe Prelude.Int,
    -- | This parameter is required for services that do not support
    -- service-linked roles (such as Amazon EMR), and it must specify the ARN
    -- of an IAM role that allows Application Auto Scaling to modify the
    -- scalable target on your behalf.
    --
    -- If the service supports service-linked roles, Application Auto Scaling
    -- uses a service-linked role, which it creates if it does not yet exist.
    -- For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/application/userguide/security_iam_service-with-iam.html#security_iam_service-with-iam-roles Application Auto Scaling IAM roles>.
    RegisterScalableTarget -> Maybe Text
roleARN :: Prelude.Maybe Prelude.Text,
    -- | An embedded object that contains attributes and attribute values that
    -- are used to suspend and resume automatic scaling. Setting the value of
    -- an attribute to @true@ suspends the specified scaling activities.
    -- Setting it to @false@ (default) resumes the specified scaling
    -- activities.
    --
    -- __Suspension Outcomes__
    --
    -- -   For @DynamicScalingInSuspended@, while a suspension is in effect,
    --     all scale-in activities that are triggered by a scaling policy are
    --     suspended.
    --
    -- -   For @DynamicScalingOutSuspended@, while a suspension is in effect,
    --     all scale-out activities that are triggered by a scaling policy are
    --     suspended.
    --
    -- -   For @ScheduledScalingSuspended@, while a suspension is in effect,
    --     all scaling activities that involve scheduled actions are suspended.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/autoscaling/application/userguide/application-auto-scaling-suspend-resume-scaling.html Suspending and resuming scaling>
    -- in the /Application Auto Scaling User Guide/.
    RegisterScalableTarget -> Maybe SuspendedState
suspendedState :: Prelude.Maybe SuspendedState,
    -- | The namespace of the Amazon Web Services service that provides the
    -- resource. For a resource provided by your own application or service,
    -- use @custom-resource@ instead.
    RegisterScalableTarget -> ServiceNamespace
serviceNamespace :: ServiceNamespace,
    -- | The identifier of the resource that is associated with the scalable
    -- target. This string consists of the resource type and unique identifier.
    --
    -- -   ECS service - The resource type is @service@ and the unique
    --     identifier is the cluster name and service name. Example:
    --     @service\/default\/sample-webapp@.
    --
    -- -   Spot Fleet - The resource type is @spot-fleet-request@ and the
    --     unique identifier is the Spot Fleet request ID. Example:
    --     @spot-fleet-request\/sfr-73fbd2ce-aa30-494c-8788-1cee4EXAMPLE@.
    --
    -- -   EMR cluster - The resource type is @instancegroup@ and the unique
    --     identifier is the cluster ID and instance group ID. Example:
    --     @instancegroup\/j-2EEZNYKUA1NTV\/ig-1791Y4E1L8YI0@.
    --
    -- -   AppStream 2.0 fleet - The resource type is @fleet@ and the unique
    --     identifier is the fleet name. Example: @fleet\/sample-fleet@.
    --
    -- -   DynamoDB table - The resource type is @table@ and the unique
    --     identifier is the table name. Example: @table\/my-table@.
    --
    -- -   DynamoDB global secondary index - The resource type is @index@ and
    --     the unique identifier is the index name. Example:
    --     @table\/my-table\/index\/my-table-index@.
    --
    -- -   Aurora DB cluster - The resource type is @cluster@ and the unique
    --     identifier is the cluster name. Example: @cluster:my-db-cluster@.
    --
    -- -   SageMaker endpoint variant - The resource type is @variant@ and the
    --     unique identifier is the resource ID. Example:
    --     @endpoint\/my-end-point\/variant\/KMeansClustering@.
    --
    -- -   Custom resources are not supported with a resource type. This
    --     parameter must specify the @OutputValue@ from the CloudFormation
    --     template stack used to access the resources. The unique identifier
    --     is defined by the service provider. More information is available in
    --     our
    --     <https://github.com/aws/aws-auto-scaling-custom-resource GitHub repository>.
    --
    -- -   Amazon Comprehend document classification endpoint - The resource
    --     type and unique identifier are specified using the endpoint ARN.
    --     Example:
    --     @arn:aws:comprehend:us-west-2:123456789012:document-classifier-endpoint\/EXAMPLE@.
    --
    -- -   Amazon Comprehend entity recognizer endpoint - The resource type and
    --     unique identifier are specified using the endpoint ARN. Example:
    --     @arn:aws:comprehend:us-west-2:123456789012:entity-recognizer-endpoint\/EXAMPLE@.
    --
    -- -   Lambda provisioned concurrency - The resource type is @function@ and
    --     the unique identifier is the function name with a function version
    --     or alias name suffix that is not @$LATEST@. Example:
    --     @function:my-function:prod@ or @function:my-function:1@.
    --
    -- -   Amazon Keyspaces table - The resource type is @table@ and the unique
    --     identifier is the table name. Example:
    --     @keyspace\/mykeyspace\/table\/mytable@.
    --
    -- -   Amazon MSK cluster - The resource type and unique identifier are
    --     specified using the cluster ARN. Example:
    --     @arn:aws:kafka:us-east-1:123456789012:cluster\/demo-cluster-1\/6357e0b2-0e6a-4b86-a0b4-70df934c2e31-5@.
    --
    -- -   Amazon ElastiCache replication group - The resource type is
    --     @replication-group@ and the unique identifier is the replication
    --     group name. Example: @replication-group\/mycluster@.
    --
    -- -   Neptune cluster - The resource type is @cluster@ and the unique
    --     identifier is the cluster name. Example: @cluster:mycluster@.
    RegisterScalableTarget -> Text
resourceId :: Prelude.Text,
    -- | The scalable dimension associated with the scalable target. This string
    -- consists of the service namespace, resource type, and scaling property.
    --
    -- -   @ecs:service:DesiredCount@ - The desired task count of an ECS
    --     service.
    --
    -- -   @elasticmapreduce:instancegroup:InstanceCount@ - The instance count
    --     of an EMR Instance Group.
    --
    -- -   @ec2:spot-fleet-request:TargetCapacity@ - The target capacity of a
    --     Spot Fleet.
    --
    -- -   @appstream:fleet:DesiredCapacity@ - The desired capacity of an
    --     AppStream 2.0 fleet.
    --
    -- -   @dynamodb:table:ReadCapacityUnits@ - The provisioned read capacity
    --     for a DynamoDB table.
    --
    -- -   @dynamodb:table:WriteCapacityUnits@ - The provisioned write capacity
    --     for a DynamoDB table.
    --
    -- -   @dynamodb:index:ReadCapacityUnits@ - The provisioned read capacity
    --     for a DynamoDB global secondary index.
    --
    -- -   @dynamodb:index:WriteCapacityUnits@ - The provisioned write capacity
    --     for a DynamoDB global secondary index.
    --
    -- -   @rds:cluster:ReadReplicaCount@ - The count of Aurora Replicas in an
    --     Aurora DB cluster. Available for Aurora MySQL-compatible edition and
    --     Aurora PostgreSQL-compatible edition.
    --
    -- -   @sagemaker:variant:DesiredInstanceCount@ - The number of EC2
    --     instances for a SageMaker model endpoint variant.
    --
    -- -   @custom-resource:ResourceType:Property@ - The scalable dimension for
    --     a custom resource provided by your own application or service.
    --
    -- -   @comprehend:document-classifier-endpoint:DesiredInferenceUnits@ -
    --     The number of inference units for an Amazon Comprehend document
    --     classification endpoint.
    --
    -- -   @comprehend:entity-recognizer-endpoint:DesiredInferenceUnits@ - The
    --     number of inference units for an Amazon Comprehend entity recognizer
    --     endpoint.
    --
    -- -   @lambda:function:ProvisionedConcurrency@ - The provisioned
    --     concurrency for a Lambda function.
    --
    -- -   @cassandra:table:ReadCapacityUnits@ - The provisioned read capacity
    --     for an Amazon Keyspaces table.
    --
    -- -   @cassandra:table:WriteCapacityUnits@ - The provisioned write
    --     capacity for an Amazon Keyspaces table.
    --
    -- -   @kafka:broker-storage:VolumeSize@ - The provisioned volume size (in
    --     GiB) for brokers in an Amazon MSK cluster.
    --
    -- -   @elasticache:replication-group:NodeGroups@ - The number of node
    --     groups for an Amazon ElastiCache replication group.
    --
    -- -   @elasticache:replication-group:Replicas@ - The number of replicas
    --     per node group for an Amazon ElastiCache replication group.
    --
    -- -   @neptune:cluster:ReadReplicaCount@ - The count of read replicas in
    --     an Amazon Neptune DB cluster.
    RegisterScalableTarget -> ScalableDimension
scalableDimension :: ScalableDimension
  }
  deriving (RegisterScalableTarget -> RegisterScalableTarget -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterScalableTarget -> RegisterScalableTarget -> Bool
$c/= :: RegisterScalableTarget -> RegisterScalableTarget -> Bool
== :: RegisterScalableTarget -> RegisterScalableTarget -> Bool
$c== :: RegisterScalableTarget -> RegisterScalableTarget -> Bool
Prelude.Eq, ReadPrec [RegisterScalableTarget]
ReadPrec RegisterScalableTarget
Int -> ReadS RegisterScalableTarget
ReadS [RegisterScalableTarget]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RegisterScalableTarget]
$creadListPrec :: ReadPrec [RegisterScalableTarget]
readPrec :: ReadPrec RegisterScalableTarget
$creadPrec :: ReadPrec RegisterScalableTarget
readList :: ReadS [RegisterScalableTarget]
$creadList :: ReadS [RegisterScalableTarget]
readsPrec :: Int -> ReadS RegisterScalableTarget
$creadsPrec :: Int -> ReadS RegisterScalableTarget
Prelude.Read, Int -> RegisterScalableTarget -> ShowS
[RegisterScalableTarget] -> ShowS
RegisterScalableTarget -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterScalableTarget] -> ShowS
$cshowList :: [RegisterScalableTarget] -> ShowS
show :: RegisterScalableTarget -> String
$cshow :: RegisterScalableTarget -> String
showsPrec :: Int -> RegisterScalableTarget -> ShowS
$cshowsPrec :: Int -> RegisterScalableTarget -> ShowS
Prelude.Show, forall x. Rep RegisterScalableTarget x -> RegisterScalableTarget
forall x. RegisterScalableTarget -> Rep RegisterScalableTarget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterScalableTarget x -> RegisterScalableTarget
$cfrom :: forall x. RegisterScalableTarget -> Rep RegisterScalableTarget x
Prelude.Generic)

-- |
-- Create a value of 'RegisterScalableTarget' 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:
--
-- 'maxCapacity', 'registerScalableTarget_maxCapacity' - The maximum value that you plan to scale out to. When a scaling policy
-- is in effect, Application Auto Scaling can scale out (expand) as needed
-- to the maximum capacity limit in response to changing demand. This
-- property is required when registering a new scalable target.
--
-- Although you can specify a large maximum capacity, note that service
-- quotas may impose lower limits. Each service has its own default quotas
-- for the maximum capacity of the resource. If you want to specify a
-- higher limit, you can request an increase. For more information, consult
-- the documentation for that service. For information about the default
-- quotas for each service, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-service-information.html Service endpoints and quotas>
-- in the /Amazon Web Services General Reference/.
--
-- 'minCapacity', 'registerScalableTarget_minCapacity' - The minimum value that you plan to scale in to. When a scaling policy is
-- in effect, Application Auto Scaling can scale in (contract) as needed to
-- the minimum capacity limit in response to changing demand. This property
-- is required when registering a new scalable target.
--
-- For the following resources, the minimum value allowed is 0.
--
-- -   AppStream 2.0 fleets
--
-- -   Aurora DB clusters
--
-- -   ECS services
--
-- -   EMR clusters
--
-- -   Lambda provisioned concurrency
--
-- -   SageMaker endpoint variants
--
-- -   Spot Fleets
--
-- -   custom resources
--
-- It\'s strongly recommended that you specify a value greater than 0. A
-- value greater than 0 means that data points are continuously reported to
-- CloudWatch that scaling policies can use to scale on a metric like
-- average CPU utilization.
--
-- For all other resources, the minimum allowed value depends on the type
-- of resource that you are using. If you provide a value that is lower
-- than what a resource can accept, an error occurs. In which case, the
-- error message will provide the minimum value that the resource can
-- accept.
--
-- 'roleARN', 'registerScalableTarget_roleARN' - This parameter is required for services that do not support
-- service-linked roles (such as Amazon EMR), and it must specify the ARN
-- of an IAM role that allows Application Auto Scaling to modify the
-- scalable target on your behalf.
--
-- If the service supports service-linked roles, Application Auto Scaling
-- uses a service-linked role, which it creates if it does not yet exist.
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/application/userguide/security_iam_service-with-iam.html#security_iam_service-with-iam-roles Application Auto Scaling IAM roles>.
--
-- 'suspendedState', 'registerScalableTarget_suspendedState' - An embedded object that contains attributes and attribute values that
-- are used to suspend and resume automatic scaling. Setting the value of
-- an attribute to @true@ suspends the specified scaling activities.
-- Setting it to @false@ (default) resumes the specified scaling
-- activities.
--
-- __Suspension Outcomes__
--
-- -   For @DynamicScalingInSuspended@, while a suspension is in effect,
--     all scale-in activities that are triggered by a scaling policy are
--     suspended.
--
-- -   For @DynamicScalingOutSuspended@, while a suspension is in effect,
--     all scale-out activities that are triggered by a scaling policy are
--     suspended.
--
-- -   For @ScheduledScalingSuspended@, while a suspension is in effect,
--     all scaling activities that involve scheduled actions are suspended.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/application/userguide/application-auto-scaling-suspend-resume-scaling.html Suspending and resuming scaling>
-- in the /Application Auto Scaling User Guide/.
--
-- 'serviceNamespace', 'registerScalableTarget_serviceNamespace' - The namespace of the Amazon Web Services service that provides the
-- resource. For a resource provided by your own application or service,
-- use @custom-resource@ instead.
--
-- 'resourceId', 'registerScalableTarget_resourceId' - The identifier of the resource that is associated with the scalable
-- target. This string consists of the resource type and unique identifier.
--
-- -   ECS service - The resource type is @service@ and the unique
--     identifier is the cluster name and service name. Example:
--     @service\/default\/sample-webapp@.
--
-- -   Spot Fleet - The resource type is @spot-fleet-request@ and the
--     unique identifier is the Spot Fleet request ID. Example:
--     @spot-fleet-request\/sfr-73fbd2ce-aa30-494c-8788-1cee4EXAMPLE@.
--
-- -   EMR cluster - The resource type is @instancegroup@ and the unique
--     identifier is the cluster ID and instance group ID. Example:
--     @instancegroup\/j-2EEZNYKUA1NTV\/ig-1791Y4E1L8YI0@.
--
-- -   AppStream 2.0 fleet - The resource type is @fleet@ and the unique
--     identifier is the fleet name. Example: @fleet\/sample-fleet@.
--
-- -   DynamoDB table - The resource type is @table@ and the unique
--     identifier is the table name. Example: @table\/my-table@.
--
-- -   DynamoDB global secondary index - The resource type is @index@ and
--     the unique identifier is the index name. Example:
--     @table\/my-table\/index\/my-table-index@.
--
-- -   Aurora DB cluster - The resource type is @cluster@ and the unique
--     identifier is the cluster name. Example: @cluster:my-db-cluster@.
--
-- -   SageMaker endpoint variant - The resource type is @variant@ and the
--     unique identifier is the resource ID. Example:
--     @endpoint\/my-end-point\/variant\/KMeansClustering@.
--
-- -   Custom resources are not supported with a resource type. This
--     parameter must specify the @OutputValue@ from the CloudFormation
--     template stack used to access the resources. The unique identifier
--     is defined by the service provider. More information is available in
--     our
--     <https://github.com/aws/aws-auto-scaling-custom-resource GitHub repository>.
--
-- -   Amazon Comprehend document classification endpoint - The resource
--     type and unique identifier are specified using the endpoint ARN.
--     Example:
--     @arn:aws:comprehend:us-west-2:123456789012:document-classifier-endpoint\/EXAMPLE@.
--
-- -   Amazon Comprehend entity recognizer endpoint - The resource type and
--     unique identifier are specified using the endpoint ARN. Example:
--     @arn:aws:comprehend:us-west-2:123456789012:entity-recognizer-endpoint\/EXAMPLE@.
--
-- -   Lambda provisioned concurrency - The resource type is @function@ and
--     the unique identifier is the function name with a function version
--     or alias name suffix that is not @$LATEST@. Example:
--     @function:my-function:prod@ or @function:my-function:1@.
--
-- -   Amazon Keyspaces table - The resource type is @table@ and the unique
--     identifier is the table name. Example:
--     @keyspace\/mykeyspace\/table\/mytable@.
--
-- -   Amazon MSK cluster - The resource type and unique identifier are
--     specified using the cluster ARN. Example:
--     @arn:aws:kafka:us-east-1:123456789012:cluster\/demo-cluster-1\/6357e0b2-0e6a-4b86-a0b4-70df934c2e31-5@.
--
-- -   Amazon ElastiCache replication group - The resource type is
--     @replication-group@ and the unique identifier is the replication
--     group name. Example: @replication-group\/mycluster@.
--
-- -   Neptune cluster - The resource type is @cluster@ and the unique
--     identifier is the cluster name. Example: @cluster:mycluster@.
--
-- 'scalableDimension', 'registerScalableTarget_scalableDimension' - The scalable dimension associated with the scalable target. This string
-- consists of the service namespace, resource type, and scaling property.
--
-- -   @ecs:service:DesiredCount@ - The desired task count of an ECS
--     service.
--
-- -   @elasticmapreduce:instancegroup:InstanceCount@ - The instance count
--     of an EMR Instance Group.
--
-- -   @ec2:spot-fleet-request:TargetCapacity@ - The target capacity of a
--     Spot Fleet.
--
-- -   @appstream:fleet:DesiredCapacity@ - The desired capacity of an
--     AppStream 2.0 fleet.
--
-- -   @dynamodb:table:ReadCapacityUnits@ - The provisioned read capacity
--     for a DynamoDB table.
--
-- -   @dynamodb:table:WriteCapacityUnits@ - The provisioned write capacity
--     for a DynamoDB table.
--
-- -   @dynamodb:index:ReadCapacityUnits@ - The provisioned read capacity
--     for a DynamoDB global secondary index.
--
-- -   @dynamodb:index:WriteCapacityUnits@ - The provisioned write capacity
--     for a DynamoDB global secondary index.
--
-- -   @rds:cluster:ReadReplicaCount@ - The count of Aurora Replicas in an
--     Aurora DB cluster. Available for Aurora MySQL-compatible edition and
--     Aurora PostgreSQL-compatible edition.
--
-- -   @sagemaker:variant:DesiredInstanceCount@ - The number of EC2
--     instances for a SageMaker model endpoint variant.
--
-- -   @custom-resource:ResourceType:Property@ - The scalable dimension for
--     a custom resource provided by your own application or service.
--
-- -   @comprehend:document-classifier-endpoint:DesiredInferenceUnits@ -
--     The number of inference units for an Amazon Comprehend document
--     classification endpoint.
--
-- -   @comprehend:entity-recognizer-endpoint:DesiredInferenceUnits@ - The
--     number of inference units for an Amazon Comprehend entity recognizer
--     endpoint.
--
-- -   @lambda:function:ProvisionedConcurrency@ - The provisioned
--     concurrency for a Lambda function.
--
-- -   @cassandra:table:ReadCapacityUnits@ - The provisioned read capacity
--     for an Amazon Keyspaces table.
--
-- -   @cassandra:table:WriteCapacityUnits@ - The provisioned write
--     capacity for an Amazon Keyspaces table.
--
-- -   @kafka:broker-storage:VolumeSize@ - The provisioned volume size (in
--     GiB) for brokers in an Amazon MSK cluster.
--
-- -   @elasticache:replication-group:NodeGroups@ - The number of node
--     groups for an Amazon ElastiCache replication group.
--
-- -   @elasticache:replication-group:Replicas@ - The number of replicas
--     per node group for an Amazon ElastiCache replication group.
--
-- -   @neptune:cluster:ReadReplicaCount@ - The count of read replicas in
--     an Amazon Neptune DB cluster.
newRegisterScalableTarget ::
  -- | 'serviceNamespace'
  ServiceNamespace ->
  -- | 'resourceId'
  Prelude.Text ->
  -- | 'scalableDimension'
  ScalableDimension ->
  RegisterScalableTarget
newRegisterScalableTarget :: ServiceNamespace
-> Text -> ScalableDimension -> RegisterScalableTarget
newRegisterScalableTarget
  ServiceNamespace
pServiceNamespace_
  Text
pResourceId_
  ScalableDimension
pScalableDimension_ =
    RegisterScalableTarget'
      { $sel:maxCapacity:RegisterScalableTarget' :: Maybe Int
maxCapacity =
          forall a. Maybe a
Prelude.Nothing,
        $sel:minCapacity:RegisterScalableTarget' :: Maybe Int
minCapacity = forall a. Maybe a
Prelude.Nothing,
        $sel:roleARN:RegisterScalableTarget' :: Maybe Text
roleARN = forall a. Maybe a
Prelude.Nothing,
        $sel:suspendedState:RegisterScalableTarget' :: Maybe SuspendedState
suspendedState = forall a. Maybe a
Prelude.Nothing,
        $sel:serviceNamespace:RegisterScalableTarget' :: ServiceNamespace
serviceNamespace = ServiceNamespace
pServiceNamespace_,
        $sel:resourceId:RegisterScalableTarget' :: Text
resourceId = Text
pResourceId_,
        $sel:scalableDimension:RegisterScalableTarget' :: ScalableDimension
scalableDimension = ScalableDimension
pScalableDimension_
      }

-- | The maximum value that you plan to scale out to. When a scaling policy
-- is in effect, Application Auto Scaling can scale out (expand) as needed
-- to the maximum capacity limit in response to changing demand. This
-- property is required when registering a new scalable target.
--
-- Although you can specify a large maximum capacity, note that service
-- quotas may impose lower limits. Each service has its own default quotas
-- for the maximum capacity of the resource. If you want to specify a
-- higher limit, you can request an increase. For more information, consult
-- the documentation for that service. For information about the default
-- quotas for each service, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-service-information.html Service endpoints and quotas>
-- in the /Amazon Web Services General Reference/.
registerScalableTarget_maxCapacity :: Lens.Lens' RegisterScalableTarget (Prelude.Maybe Prelude.Int)
registerScalableTarget_maxCapacity :: Lens' RegisterScalableTarget (Maybe Int)
registerScalableTarget_maxCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterScalableTarget' {Maybe Int
maxCapacity :: Maybe Int
$sel:maxCapacity:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Int
maxCapacity} -> Maybe Int
maxCapacity) (\s :: RegisterScalableTarget
s@RegisterScalableTarget' {} Maybe Int
a -> RegisterScalableTarget
s {$sel:maxCapacity:RegisterScalableTarget' :: Maybe Int
maxCapacity = Maybe Int
a} :: RegisterScalableTarget)

-- | The minimum value that you plan to scale in to. When a scaling policy is
-- in effect, Application Auto Scaling can scale in (contract) as needed to
-- the minimum capacity limit in response to changing demand. This property
-- is required when registering a new scalable target.
--
-- For the following resources, the minimum value allowed is 0.
--
-- -   AppStream 2.0 fleets
--
-- -   Aurora DB clusters
--
-- -   ECS services
--
-- -   EMR clusters
--
-- -   Lambda provisioned concurrency
--
-- -   SageMaker endpoint variants
--
-- -   Spot Fleets
--
-- -   custom resources
--
-- It\'s strongly recommended that you specify a value greater than 0. A
-- value greater than 0 means that data points are continuously reported to
-- CloudWatch that scaling policies can use to scale on a metric like
-- average CPU utilization.
--
-- For all other resources, the minimum allowed value depends on the type
-- of resource that you are using. If you provide a value that is lower
-- than what a resource can accept, an error occurs. In which case, the
-- error message will provide the minimum value that the resource can
-- accept.
registerScalableTarget_minCapacity :: Lens.Lens' RegisterScalableTarget (Prelude.Maybe Prelude.Int)
registerScalableTarget_minCapacity :: Lens' RegisterScalableTarget (Maybe Int)
registerScalableTarget_minCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterScalableTarget' {Maybe Int
minCapacity :: Maybe Int
$sel:minCapacity:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Int
minCapacity} -> Maybe Int
minCapacity) (\s :: RegisterScalableTarget
s@RegisterScalableTarget' {} Maybe Int
a -> RegisterScalableTarget
s {$sel:minCapacity:RegisterScalableTarget' :: Maybe Int
minCapacity = Maybe Int
a} :: RegisterScalableTarget)

-- | This parameter is required for services that do not support
-- service-linked roles (such as Amazon EMR), and it must specify the ARN
-- of an IAM role that allows Application Auto Scaling to modify the
-- scalable target on your behalf.
--
-- If the service supports service-linked roles, Application Auto Scaling
-- uses a service-linked role, which it creates if it does not yet exist.
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/application/userguide/security_iam_service-with-iam.html#security_iam_service-with-iam-roles Application Auto Scaling IAM roles>.
registerScalableTarget_roleARN :: Lens.Lens' RegisterScalableTarget (Prelude.Maybe Prelude.Text)
registerScalableTarget_roleARN :: Lens' RegisterScalableTarget (Maybe Text)
registerScalableTarget_roleARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterScalableTarget' {Maybe Text
roleARN :: Maybe Text
$sel:roleARN:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Text
roleARN} -> Maybe Text
roleARN) (\s :: RegisterScalableTarget
s@RegisterScalableTarget' {} Maybe Text
a -> RegisterScalableTarget
s {$sel:roleARN:RegisterScalableTarget' :: Maybe Text
roleARN = Maybe Text
a} :: RegisterScalableTarget)

-- | An embedded object that contains attributes and attribute values that
-- are used to suspend and resume automatic scaling. Setting the value of
-- an attribute to @true@ suspends the specified scaling activities.
-- Setting it to @false@ (default) resumes the specified scaling
-- activities.
--
-- __Suspension Outcomes__
--
-- -   For @DynamicScalingInSuspended@, while a suspension is in effect,
--     all scale-in activities that are triggered by a scaling policy are
--     suspended.
--
-- -   For @DynamicScalingOutSuspended@, while a suspension is in effect,
--     all scale-out activities that are triggered by a scaling policy are
--     suspended.
--
-- -   For @ScheduledScalingSuspended@, while a suspension is in effect,
--     all scaling activities that involve scheduled actions are suspended.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/application/userguide/application-auto-scaling-suspend-resume-scaling.html Suspending and resuming scaling>
-- in the /Application Auto Scaling User Guide/.
registerScalableTarget_suspendedState :: Lens.Lens' RegisterScalableTarget (Prelude.Maybe SuspendedState)
registerScalableTarget_suspendedState :: Lens' RegisterScalableTarget (Maybe SuspendedState)
registerScalableTarget_suspendedState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterScalableTarget' {Maybe SuspendedState
suspendedState :: Maybe SuspendedState
$sel:suspendedState:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe SuspendedState
suspendedState} -> Maybe SuspendedState
suspendedState) (\s :: RegisterScalableTarget
s@RegisterScalableTarget' {} Maybe SuspendedState
a -> RegisterScalableTarget
s {$sel:suspendedState:RegisterScalableTarget' :: Maybe SuspendedState
suspendedState = Maybe SuspendedState
a} :: RegisterScalableTarget)

-- | The namespace of the Amazon Web Services service that provides the
-- resource. For a resource provided by your own application or service,
-- use @custom-resource@ instead.
registerScalableTarget_serviceNamespace :: Lens.Lens' RegisterScalableTarget ServiceNamespace
registerScalableTarget_serviceNamespace :: Lens' RegisterScalableTarget ServiceNamespace
registerScalableTarget_serviceNamespace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterScalableTarget' {ServiceNamespace
serviceNamespace :: ServiceNamespace
$sel:serviceNamespace:RegisterScalableTarget' :: RegisterScalableTarget -> ServiceNamespace
serviceNamespace} -> ServiceNamespace
serviceNamespace) (\s :: RegisterScalableTarget
s@RegisterScalableTarget' {} ServiceNamespace
a -> RegisterScalableTarget
s {$sel:serviceNamespace:RegisterScalableTarget' :: ServiceNamespace
serviceNamespace = ServiceNamespace
a} :: RegisterScalableTarget)

-- | The identifier of the resource that is associated with the scalable
-- target. This string consists of the resource type and unique identifier.
--
-- -   ECS service - The resource type is @service@ and the unique
--     identifier is the cluster name and service name. Example:
--     @service\/default\/sample-webapp@.
--
-- -   Spot Fleet - The resource type is @spot-fleet-request@ and the
--     unique identifier is the Spot Fleet request ID. Example:
--     @spot-fleet-request\/sfr-73fbd2ce-aa30-494c-8788-1cee4EXAMPLE@.
--
-- -   EMR cluster - The resource type is @instancegroup@ and the unique
--     identifier is the cluster ID and instance group ID. Example:
--     @instancegroup\/j-2EEZNYKUA1NTV\/ig-1791Y4E1L8YI0@.
--
-- -   AppStream 2.0 fleet - The resource type is @fleet@ and the unique
--     identifier is the fleet name. Example: @fleet\/sample-fleet@.
--
-- -   DynamoDB table - The resource type is @table@ and the unique
--     identifier is the table name. Example: @table\/my-table@.
--
-- -   DynamoDB global secondary index - The resource type is @index@ and
--     the unique identifier is the index name. Example:
--     @table\/my-table\/index\/my-table-index@.
--
-- -   Aurora DB cluster - The resource type is @cluster@ and the unique
--     identifier is the cluster name. Example: @cluster:my-db-cluster@.
--
-- -   SageMaker endpoint variant - The resource type is @variant@ and the
--     unique identifier is the resource ID. Example:
--     @endpoint\/my-end-point\/variant\/KMeansClustering@.
--
-- -   Custom resources are not supported with a resource type. This
--     parameter must specify the @OutputValue@ from the CloudFormation
--     template stack used to access the resources. The unique identifier
--     is defined by the service provider. More information is available in
--     our
--     <https://github.com/aws/aws-auto-scaling-custom-resource GitHub repository>.
--
-- -   Amazon Comprehend document classification endpoint - The resource
--     type and unique identifier are specified using the endpoint ARN.
--     Example:
--     @arn:aws:comprehend:us-west-2:123456789012:document-classifier-endpoint\/EXAMPLE@.
--
-- -   Amazon Comprehend entity recognizer endpoint - The resource type and
--     unique identifier are specified using the endpoint ARN. Example:
--     @arn:aws:comprehend:us-west-2:123456789012:entity-recognizer-endpoint\/EXAMPLE@.
--
-- -   Lambda provisioned concurrency - The resource type is @function@ and
--     the unique identifier is the function name with a function version
--     or alias name suffix that is not @$LATEST@. Example:
--     @function:my-function:prod@ or @function:my-function:1@.
--
-- -   Amazon Keyspaces table - The resource type is @table@ and the unique
--     identifier is the table name. Example:
--     @keyspace\/mykeyspace\/table\/mytable@.
--
-- -   Amazon MSK cluster - The resource type and unique identifier are
--     specified using the cluster ARN. Example:
--     @arn:aws:kafka:us-east-1:123456789012:cluster\/demo-cluster-1\/6357e0b2-0e6a-4b86-a0b4-70df934c2e31-5@.
--
-- -   Amazon ElastiCache replication group - The resource type is
--     @replication-group@ and the unique identifier is the replication
--     group name. Example: @replication-group\/mycluster@.
--
-- -   Neptune cluster - The resource type is @cluster@ and the unique
--     identifier is the cluster name. Example: @cluster:mycluster@.
registerScalableTarget_resourceId :: Lens.Lens' RegisterScalableTarget Prelude.Text
registerScalableTarget_resourceId :: Lens' RegisterScalableTarget Text
registerScalableTarget_resourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterScalableTarget' {Text
resourceId :: Text
$sel:resourceId:RegisterScalableTarget' :: RegisterScalableTarget -> Text
resourceId} -> Text
resourceId) (\s :: RegisterScalableTarget
s@RegisterScalableTarget' {} Text
a -> RegisterScalableTarget
s {$sel:resourceId:RegisterScalableTarget' :: Text
resourceId = Text
a} :: RegisterScalableTarget)

-- | The scalable dimension associated with the scalable target. This string
-- consists of the service namespace, resource type, and scaling property.
--
-- -   @ecs:service:DesiredCount@ - The desired task count of an ECS
--     service.
--
-- -   @elasticmapreduce:instancegroup:InstanceCount@ - The instance count
--     of an EMR Instance Group.
--
-- -   @ec2:spot-fleet-request:TargetCapacity@ - The target capacity of a
--     Spot Fleet.
--
-- -   @appstream:fleet:DesiredCapacity@ - The desired capacity of an
--     AppStream 2.0 fleet.
--
-- -   @dynamodb:table:ReadCapacityUnits@ - The provisioned read capacity
--     for a DynamoDB table.
--
-- -   @dynamodb:table:WriteCapacityUnits@ - The provisioned write capacity
--     for a DynamoDB table.
--
-- -   @dynamodb:index:ReadCapacityUnits@ - The provisioned read capacity
--     for a DynamoDB global secondary index.
--
-- -   @dynamodb:index:WriteCapacityUnits@ - The provisioned write capacity
--     for a DynamoDB global secondary index.
--
-- -   @rds:cluster:ReadReplicaCount@ - The count of Aurora Replicas in an
--     Aurora DB cluster. Available for Aurora MySQL-compatible edition and
--     Aurora PostgreSQL-compatible edition.
--
-- -   @sagemaker:variant:DesiredInstanceCount@ - The number of EC2
--     instances for a SageMaker model endpoint variant.
--
-- -   @custom-resource:ResourceType:Property@ - The scalable dimension for
--     a custom resource provided by your own application or service.
--
-- -   @comprehend:document-classifier-endpoint:DesiredInferenceUnits@ -
--     The number of inference units for an Amazon Comprehend document
--     classification endpoint.
--
-- -   @comprehend:entity-recognizer-endpoint:DesiredInferenceUnits@ - The
--     number of inference units for an Amazon Comprehend entity recognizer
--     endpoint.
--
-- -   @lambda:function:ProvisionedConcurrency@ - The provisioned
--     concurrency for a Lambda function.
--
-- -   @cassandra:table:ReadCapacityUnits@ - The provisioned read capacity
--     for an Amazon Keyspaces table.
--
-- -   @cassandra:table:WriteCapacityUnits@ - The provisioned write
--     capacity for an Amazon Keyspaces table.
--
-- -   @kafka:broker-storage:VolumeSize@ - The provisioned volume size (in
--     GiB) for brokers in an Amazon MSK cluster.
--
-- -   @elasticache:replication-group:NodeGroups@ - The number of node
--     groups for an Amazon ElastiCache replication group.
--
-- -   @elasticache:replication-group:Replicas@ - The number of replicas
--     per node group for an Amazon ElastiCache replication group.
--
-- -   @neptune:cluster:ReadReplicaCount@ - The count of read replicas in
--     an Amazon Neptune DB cluster.
registerScalableTarget_scalableDimension :: Lens.Lens' RegisterScalableTarget ScalableDimension
registerScalableTarget_scalableDimension :: Lens' RegisterScalableTarget ScalableDimension
registerScalableTarget_scalableDimension = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterScalableTarget' {ScalableDimension
scalableDimension :: ScalableDimension
$sel:scalableDimension:RegisterScalableTarget' :: RegisterScalableTarget -> ScalableDimension
scalableDimension} -> ScalableDimension
scalableDimension) (\s :: RegisterScalableTarget
s@RegisterScalableTarget' {} ScalableDimension
a -> RegisterScalableTarget
s {$sel:scalableDimension:RegisterScalableTarget' :: ScalableDimension
scalableDimension = ScalableDimension
a} :: RegisterScalableTarget)

instance Core.AWSRequest RegisterScalableTarget where
  type
    AWSResponse RegisterScalableTarget =
      RegisterScalableTargetResponse
  request :: (Service -> Service)
-> RegisterScalableTarget -> Request RegisterScalableTarget
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 RegisterScalableTarget
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RegisterScalableTarget)))
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 -> RegisterScalableTargetResponse
RegisterScalableTargetResponse'
            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 RegisterScalableTarget where
  hashWithSalt :: Int -> RegisterScalableTarget -> Int
hashWithSalt Int
_salt RegisterScalableTarget' {Maybe Int
Maybe Text
Maybe SuspendedState
Text
ScalableDimension
ServiceNamespace
scalableDimension :: ScalableDimension
resourceId :: Text
serviceNamespace :: ServiceNamespace
suspendedState :: Maybe SuspendedState
roleARN :: Maybe Text
minCapacity :: Maybe Int
maxCapacity :: Maybe Int
$sel:scalableDimension:RegisterScalableTarget' :: RegisterScalableTarget -> ScalableDimension
$sel:resourceId:RegisterScalableTarget' :: RegisterScalableTarget -> Text
$sel:serviceNamespace:RegisterScalableTarget' :: RegisterScalableTarget -> ServiceNamespace
$sel:suspendedState:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe SuspendedState
$sel:roleARN:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Text
$sel:minCapacity:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Int
$sel:maxCapacity:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
minCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SuspendedState
suspendedState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ServiceNamespace
serviceNamespace
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ScalableDimension
scalableDimension

instance Prelude.NFData RegisterScalableTarget where
  rnf :: RegisterScalableTarget -> ()
rnf RegisterScalableTarget' {Maybe Int
Maybe Text
Maybe SuspendedState
Text
ScalableDimension
ServiceNamespace
scalableDimension :: ScalableDimension
resourceId :: Text
serviceNamespace :: ServiceNamespace
suspendedState :: Maybe SuspendedState
roleARN :: Maybe Text
minCapacity :: Maybe Int
maxCapacity :: Maybe Int
$sel:scalableDimension:RegisterScalableTarget' :: RegisterScalableTarget -> ScalableDimension
$sel:resourceId:RegisterScalableTarget' :: RegisterScalableTarget -> Text
$sel:serviceNamespace:RegisterScalableTarget' :: RegisterScalableTarget -> ServiceNamespace
$sel:suspendedState:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe SuspendedState
$sel:roleARN:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Text
$sel:minCapacity:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Int
$sel:maxCapacity:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
minCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SuspendedState
suspendedState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ServiceNamespace
serviceNamespace
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ScalableDimension
scalableDimension

instance Data.ToHeaders RegisterScalableTarget where
  toHeaders :: RegisterScalableTarget -> 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
"AnyScaleFrontendService.RegisterScalableTarget" ::
                          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 RegisterScalableTarget where
  toJSON :: RegisterScalableTarget -> Value
toJSON RegisterScalableTarget' {Maybe Int
Maybe Text
Maybe SuspendedState
Text
ScalableDimension
ServiceNamespace
scalableDimension :: ScalableDimension
resourceId :: Text
serviceNamespace :: ServiceNamespace
suspendedState :: Maybe SuspendedState
roleARN :: Maybe Text
minCapacity :: Maybe Int
maxCapacity :: Maybe Int
$sel:scalableDimension:RegisterScalableTarget' :: RegisterScalableTarget -> ScalableDimension
$sel:resourceId:RegisterScalableTarget' :: RegisterScalableTarget -> Text
$sel:serviceNamespace:RegisterScalableTarget' :: RegisterScalableTarget -> ServiceNamespace
$sel:suspendedState:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe SuspendedState
$sel:roleARN:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Text
$sel:minCapacity:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Int
$sel:maxCapacity:RegisterScalableTarget' :: RegisterScalableTarget -> Maybe Int
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaxCapacity" 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 Int
maxCapacity,
            (Key
"MinCapacity" 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 Int
minCapacity,
            (Key
"RoleARN" 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 Text
roleARN,
            (Key
"SuspendedState" 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 SuspendedState
suspendedState,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ServiceNamespace" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ServiceNamespace
serviceNamespace),
            forall a. a -> Maybe a
Prelude.Just (Key
"ResourceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ScalableDimension" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ScalableDimension
scalableDimension)
          ]
      )

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

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

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

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

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

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