{-# 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.EMR.PutManagedScalingPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates or updates a managed scaling policy for an Amazon EMR cluster.
-- The managed scaling policy defines the limits for resources, such as EC2
-- instances that can be added or terminated from a cluster. The policy
-- only applies to the core and task nodes. The master node cannot be
-- scaled after initial configuration.
module Amazonka.EMR.PutManagedScalingPolicy
  ( -- * Creating a Request
    PutManagedScalingPolicy (..),
    newPutManagedScalingPolicy,

    -- * Request Lenses
    putManagedScalingPolicy_clusterId,
    putManagedScalingPolicy_managedScalingPolicy,

    -- * Destructuring the Response
    PutManagedScalingPolicyResponse (..),
    newPutManagedScalingPolicyResponse,

    -- * Response Lenses
    putManagedScalingPolicyResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EMR.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newPutManagedScalingPolicy' smart constructor.
data PutManagedScalingPolicy = PutManagedScalingPolicy'
  { -- | Specifies the ID of an EMR cluster where the managed scaling policy is
    -- attached.
    PutManagedScalingPolicy -> Text
clusterId :: Prelude.Text,
    -- | Specifies the constraints for the managed scaling policy.
    PutManagedScalingPolicy -> ManagedScalingPolicy
managedScalingPolicy :: ManagedScalingPolicy
  }
  deriving (PutManagedScalingPolicy -> PutManagedScalingPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutManagedScalingPolicy -> PutManagedScalingPolicy -> Bool
$c/= :: PutManagedScalingPolicy -> PutManagedScalingPolicy -> Bool
== :: PutManagedScalingPolicy -> PutManagedScalingPolicy -> Bool
$c== :: PutManagedScalingPolicy -> PutManagedScalingPolicy -> Bool
Prelude.Eq, ReadPrec [PutManagedScalingPolicy]
ReadPrec PutManagedScalingPolicy
Int -> ReadS PutManagedScalingPolicy
ReadS [PutManagedScalingPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutManagedScalingPolicy]
$creadListPrec :: ReadPrec [PutManagedScalingPolicy]
readPrec :: ReadPrec PutManagedScalingPolicy
$creadPrec :: ReadPrec PutManagedScalingPolicy
readList :: ReadS [PutManagedScalingPolicy]
$creadList :: ReadS [PutManagedScalingPolicy]
readsPrec :: Int -> ReadS PutManagedScalingPolicy
$creadsPrec :: Int -> ReadS PutManagedScalingPolicy
Prelude.Read, Int -> PutManagedScalingPolicy -> ShowS
[PutManagedScalingPolicy] -> ShowS
PutManagedScalingPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutManagedScalingPolicy] -> ShowS
$cshowList :: [PutManagedScalingPolicy] -> ShowS
show :: PutManagedScalingPolicy -> String
$cshow :: PutManagedScalingPolicy -> String
showsPrec :: Int -> PutManagedScalingPolicy -> ShowS
$cshowsPrec :: Int -> PutManagedScalingPolicy -> ShowS
Prelude.Show, forall x. Rep PutManagedScalingPolicy x -> PutManagedScalingPolicy
forall x. PutManagedScalingPolicy -> Rep PutManagedScalingPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutManagedScalingPolicy x -> PutManagedScalingPolicy
$cfrom :: forall x. PutManagedScalingPolicy -> Rep PutManagedScalingPolicy x
Prelude.Generic)

-- |
-- Create a value of 'PutManagedScalingPolicy' 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:
--
-- 'clusterId', 'putManagedScalingPolicy_clusterId' - Specifies the ID of an EMR cluster where the managed scaling policy is
-- attached.
--
-- 'managedScalingPolicy', 'putManagedScalingPolicy_managedScalingPolicy' - Specifies the constraints for the managed scaling policy.
newPutManagedScalingPolicy ::
  -- | 'clusterId'
  Prelude.Text ->
  -- | 'managedScalingPolicy'
  ManagedScalingPolicy ->
  PutManagedScalingPolicy
newPutManagedScalingPolicy :: Text -> ManagedScalingPolicy -> PutManagedScalingPolicy
newPutManagedScalingPolicy
  Text
pClusterId_
  ManagedScalingPolicy
pManagedScalingPolicy_ =
    PutManagedScalingPolicy'
      { $sel:clusterId:PutManagedScalingPolicy' :: Text
clusterId = Text
pClusterId_,
        $sel:managedScalingPolicy:PutManagedScalingPolicy' :: ManagedScalingPolicy
managedScalingPolicy = ManagedScalingPolicy
pManagedScalingPolicy_
      }

-- | Specifies the ID of an EMR cluster where the managed scaling policy is
-- attached.
putManagedScalingPolicy_clusterId :: Lens.Lens' PutManagedScalingPolicy Prelude.Text
putManagedScalingPolicy_clusterId :: Lens' PutManagedScalingPolicy Text
putManagedScalingPolicy_clusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutManagedScalingPolicy' {Text
clusterId :: Text
$sel:clusterId:PutManagedScalingPolicy' :: PutManagedScalingPolicy -> Text
clusterId} -> Text
clusterId) (\s :: PutManagedScalingPolicy
s@PutManagedScalingPolicy' {} Text
a -> PutManagedScalingPolicy
s {$sel:clusterId:PutManagedScalingPolicy' :: Text
clusterId = Text
a} :: PutManagedScalingPolicy)

-- | Specifies the constraints for the managed scaling policy.
putManagedScalingPolicy_managedScalingPolicy :: Lens.Lens' PutManagedScalingPolicy ManagedScalingPolicy
putManagedScalingPolicy_managedScalingPolicy :: Lens' PutManagedScalingPolicy ManagedScalingPolicy
putManagedScalingPolicy_managedScalingPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutManagedScalingPolicy' {ManagedScalingPolicy
managedScalingPolicy :: ManagedScalingPolicy
$sel:managedScalingPolicy:PutManagedScalingPolicy' :: PutManagedScalingPolicy -> ManagedScalingPolicy
managedScalingPolicy} -> ManagedScalingPolicy
managedScalingPolicy) (\s :: PutManagedScalingPolicy
s@PutManagedScalingPolicy' {} ManagedScalingPolicy
a -> PutManagedScalingPolicy
s {$sel:managedScalingPolicy:PutManagedScalingPolicy' :: ManagedScalingPolicy
managedScalingPolicy = ManagedScalingPolicy
a} :: PutManagedScalingPolicy)

instance Core.AWSRequest PutManagedScalingPolicy where
  type
    AWSResponse PutManagedScalingPolicy =
      PutManagedScalingPolicyResponse
  request :: (Service -> Service)
-> PutManagedScalingPolicy -> Request PutManagedScalingPolicy
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 PutManagedScalingPolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutManagedScalingPolicy)))
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 -> PutManagedScalingPolicyResponse
PutManagedScalingPolicyResponse'
            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 PutManagedScalingPolicy where
  hashWithSalt :: Int -> PutManagedScalingPolicy -> Int
hashWithSalt Int
_salt PutManagedScalingPolicy' {Text
ManagedScalingPolicy
managedScalingPolicy :: ManagedScalingPolicy
clusterId :: Text
$sel:managedScalingPolicy:PutManagedScalingPolicy' :: PutManagedScalingPolicy -> ManagedScalingPolicy
$sel:clusterId:PutManagedScalingPolicy' :: PutManagedScalingPolicy -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ManagedScalingPolicy
managedScalingPolicy

instance Prelude.NFData PutManagedScalingPolicy where
  rnf :: PutManagedScalingPolicy -> ()
rnf PutManagedScalingPolicy' {Text
ManagedScalingPolicy
managedScalingPolicy :: ManagedScalingPolicy
clusterId :: Text
$sel:managedScalingPolicy:PutManagedScalingPolicy' :: PutManagedScalingPolicy -> ManagedScalingPolicy
$sel:clusterId:PutManagedScalingPolicy' :: PutManagedScalingPolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
clusterId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ManagedScalingPolicy
managedScalingPolicy

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

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

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

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

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

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

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