{-# 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.AutoScaling.EnterStandby
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Moves the specified instances into the standby state.
--
-- If you choose to decrement the desired capacity of the Auto Scaling
-- group, the instances can enter standby as long as the desired capacity
-- of the Auto Scaling group after the instances are placed into standby is
-- equal to or greater than the minimum capacity of the group.
--
-- If you choose not to decrement the desired capacity of the Auto Scaling
-- group, the Auto Scaling group launches new instances to replace the
-- instances on standby.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/as-enter-exit-standby.html Temporarily removing instances from your Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
module Amazonka.AutoScaling.EnterStandby
  ( -- * Creating a Request
    EnterStandby (..),
    newEnterStandby,

    -- * Request Lenses
    enterStandby_instanceIds,
    enterStandby_autoScalingGroupName,
    enterStandby_shouldDecrementDesiredCapacity,

    -- * Destructuring the Response
    EnterStandbyResponse (..),
    newEnterStandbyResponse,

    -- * Response Lenses
    enterStandbyResponse_activities,
    enterStandbyResponse_httpStatus,
  )
where

import Amazonka.AutoScaling.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:/ 'newEnterStandby' smart constructor.
data EnterStandby = EnterStandby'
  { -- | The IDs of the instances. You can specify up to 20 instances.
    EnterStandby -> Maybe [Text]
instanceIds :: Prelude.Maybe [Prelude.Text],
    -- | The name of the Auto Scaling group.
    EnterStandby -> Text
autoScalingGroupName :: Prelude.Text,
    -- | Indicates whether to decrement the desired capacity of the Auto Scaling
    -- group by the number of instances moved to @Standby@ mode.
    EnterStandby -> Bool
shouldDecrementDesiredCapacity :: Prelude.Bool
  }
  deriving (EnterStandby -> EnterStandby -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnterStandby -> EnterStandby -> Bool
$c/= :: EnterStandby -> EnterStandby -> Bool
== :: EnterStandby -> EnterStandby -> Bool
$c== :: EnterStandby -> EnterStandby -> Bool
Prelude.Eq, ReadPrec [EnterStandby]
ReadPrec EnterStandby
Int -> ReadS EnterStandby
ReadS [EnterStandby]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnterStandby]
$creadListPrec :: ReadPrec [EnterStandby]
readPrec :: ReadPrec EnterStandby
$creadPrec :: ReadPrec EnterStandby
readList :: ReadS [EnterStandby]
$creadList :: ReadS [EnterStandby]
readsPrec :: Int -> ReadS EnterStandby
$creadsPrec :: Int -> ReadS EnterStandby
Prelude.Read, Int -> EnterStandby -> ShowS
[EnterStandby] -> ShowS
EnterStandby -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnterStandby] -> ShowS
$cshowList :: [EnterStandby] -> ShowS
show :: EnterStandby -> String
$cshow :: EnterStandby -> String
showsPrec :: Int -> EnterStandby -> ShowS
$cshowsPrec :: Int -> EnterStandby -> ShowS
Prelude.Show, forall x. Rep EnterStandby x -> EnterStandby
forall x. EnterStandby -> Rep EnterStandby x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnterStandby x -> EnterStandby
$cfrom :: forall x. EnterStandby -> Rep EnterStandby x
Prelude.Generic)

-- |
-- Create a value of 'EnterStandby' 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:
--
-- 'instanceIds', 'enterStandby_instanceIds' - The IDs of the instances. You can specify up to 20 instances.
--
-- 'autoScalingGroupName', 'enterStandby_autoScalingGroupName' - The name of the Auto Scaling group.
--
-- 'shouldDecrementDesiredCapacity', 'enterStandby_shouldDecrementDesiredCapacity' - Indicates whether to decrement the desired capacity of the Auto Scaling
-- group by the number of instances moved to @Standby@ mode.
newEnterStandby ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  -- | 'shouldDecrementDesiredCapacity'
  Prelude.Bool ->
  EnterStandby
newEnterStandby :: Text -> Bool -> EnterStandby
newEnterStandby
  Text
pAutoScalingGroupName_
  Bool
pShouldDecrementDesiredCapacity_ =
    EnterStandby'
      { $sel:instanceIds:EnterStandby' :: Maybe [Text]
instanceIds = forall a. Maybe a
Prelude.Nothing,
        $sel:autoScalingGroupName:EnterStandby' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_,
        $sel:shouldDecrementDesiredCapacity:EnterStandby' :: Bool
shouldDecrementDesiredCapacity =
          Bool
pShouldDecrementDesiredCapacity_
      }

-- | The IDs of the instances. You can specify up to 20 instances.
enterStandby_instanceIds :: Lens.Lens' EnterStandby (Prelude.Maybe [Prelude.Text])
enterStandby_instanceIds :: Lens' EnterStandby (Maybe [Text])
enterStandby_instanceIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnterStandby' {Maybe [Text]
instanceIds :: Maybe [Text]
$sel:instanceIds:EnterStandby' :: EnterStandby -> Maybe [Text]
instanceIds} -> Maybe [Text]
instanceIds) (\s :: EnterStandby
s@EnterStandby' {} Maybe [Text]
a -> EnterStandby
s {$sel:instanceIds:EnterStandby' :: Maybe [Text]
instanceIds = Maybe [Text]
a} :: EnterStandby) 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 Auto Scaling group.
enterStandby_autoScalingGroupName :: Lens.Lens' EnterStandby Prelude.Text
enterStandby_autoScalingGroupName :: Lens' EnterStandby Text
enterStandby_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnterStandby' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:EnterStandby' :: EnterStandby -> Text
autoScalingGroupName} -> Text
autoScalingGroupName) (\s :: EnterStandby
s@EnterStandby' {} Text
a -> EnterStandby
s {$sel:autoScalingGroupName:EnterStandby' :: Text
autoScalingGroupName = Text
a} :: EnterStandby)

-- | Indicates whether to decrement the desired capacity of the Auto Scaling
-- group by the number of instances moved to @Standby@ mode.
enterStandby_shouldDecrementDesiredCapacity :: Lens.Lens' EnterStandby Prelude.Bool
enterStandby_shouldDecrementDesiredCapacity :: Lens' EnterStandby Bool
enterStandby_shouldDecrementDesiredCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnterStandby' {Bool
shouldDecrementDesiredCapacity :: Bool
$sel:shouldDecrementDesiredCapacity:EnterStandby' :: EnterStandby -> Bool
shouldDecrementDesiredCapacity} -> Bool
shouldDecrementDesiredCapacity) (\s :: EnterStandby
s@EnterStandby' {} Bool
a -> EnterStandby
s {$sel:shouldDecrementDesiredCapacity:EnterStandby' :: Bool
shouldDecrementDesiredCapacity = Bool
a} :: EnterStandby)

instance Core.AWSRequest EnterStandby where
  type AWSResponse EnterStandby = EnterStandbyResponse
  request :: (Service -> Service) -> EnterStandby -> Request EnterStandby
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy EnterStandby
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse EnterStandby)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"EnterStandbyResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [Activity] -> Int -> EnterStandbyResponse
EnterStandbyResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Activities"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            forall (f :: * -> *) a b. Applicative f => 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 EnterStandby where
  hashWithSalt :: Int -> EnterStandby -> Int
hashWithSalt Int
_salt EnterStandby' {Bool
Maybe [Text]
Text
shouldDecrementDesiredCapacity :: Bool
autoScalingGroupName :: Text
instanceIds :: Maybe [Text]
$sel:shouldDecrementDesiredCapacity:EnterStandby' :: EnterStandby -> Bool
$sel:autoScalingGroupName:EnterStandby' :: EnterStandby -> Text
$sel:instanceIds:EnterStandby' :: EnterStandby -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
instanceIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Bool
shouldDecrementDesiredCapacity

instance Prelude.NFData EnterStandby where
  rnf :: EnterStandby -> ()
rnf EnterStandby' {Bool
Maybe [Text]
Text
shouldDecrementDesiredCapacity :: Bool
autoScalingGroupName :: Text
instanceIds :: Maybe [Text]
$sel:shouldDecrementDesiredCapacity:EnterStandby' :: EnterStandby -> Bool
$sel:autoScalingGroupName:EnterStandby' :: EnterStandby -> Text
$sel:instanceIds:EnterStandby' :: EnterStandby -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
instanceIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
autoScalingGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
shouldDecrementDesiredCapacity

instance Data.ToHeaders EnterStandby where
  toHeaders :: EnterStandby -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery EnterStandby where
  toQuery :: EnterStandby -> QueryString
toQuery EnterStandby' {Bool
Maybe [Text]
Text
shouldDecrementDesiredCapacity :: Bool
autoScalingGroupName :: Text
instanceIds :: Maybe [Text]
$sel:shouldDecrementDesiredCapacity:EnterStandby' :: EnterStandby -> Bool
$sel:autoScalingGroupName:EnterStandby' :: EnterStandby -> Text
$sel:instanceIds:EnterStandby' :: EnterStandby -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"EnterStandby" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-01-01" :: Prelude.ByteString),
        ByteString
"InstanceIds"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
instanceIds),
        ByteString
"AutoScalingGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
autoScalingGroupName,
        ByteString
"ShouldDecrementDesiredCapacity"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Bool
shouldDecrementDesiredCapacity
      ]

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

-- |
-- Create a value of 'EnterStandbyResponse' 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:
--
-- 'activities', 'enterStandbyResponse_activities' - The activities related to moving instances into @Standby@ mode.
--
-- 'httpStatus', 'enterStandbyResponse_httpStatus' - The response's http status code.
newEnterStandbyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  EnterStandbyResponse
newEnterStandbyResponse :: Int -> EnterStandbyResponse
newEnterStandbyResponse Int
pHttpStatus_ =
  EnterStandbyResponse'
    { $sel:activities:EnterStandbyResponse' :: Maybe [Activity]
activities = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:EnterStandbyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The activities related to moving instances into @Standby@ mode.
enterStandbyResponse_activities :: Lens.Lens' EnterStandbyResponse (Prelude.Maybe [Activity])
enterStandbyResponse_activities :: Lens' EnterStandbyResponse (Maybe [Activity])
enterStandbyResponse_activities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnterStandbyResponse' {Maybe [Activity]
activities :: Maybe [Activity]
$sel:activities:EnterStandbyResponse' :: EnterStandbyResponse -> Maybe [Activity]
activities} -> Maybe [Activity]
activities) (\s :: EnterStandbyResponse
s@EnterStandbyResponse' {} Maybe [Activity]
a -> EnterStandbyResponse
s {$sel:activities:EnterStandbyResponse' :: Maybe [Activity]
activities = Maybe [Activity]
a} :: EnterStandbyResponse) 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 response's http status code.
enterStandbyResponse_httpStatus :: Lens.Lens' EnterStandbyResponse Prelude.Int
enterStandbyResponse_httpStatus :: Lens' EnterStandbyResponse Int
enterStandbyResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnterStandbyResponse' {Int
httpStatus :: Int
$sel:httpStatus:EnterStandbyResponse' :: EnterStandbyResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: EnterStandbyResponse
s@EnterStandbyResponse' {} Int
a -> EnterStandbyResponse
s {$sel:httpStatus:EnterStandbyResponse' :: Int
httpStatus = Int
a} :: EnterStandbyResponse)

instance Prelude.NFData EnterStandbyResponse where
  rnf :: EnterStandbyResponse -> ()
rnf EnterStandbyResponse' {Int
Maybe [Activity]
httpStatus :: Int
activities :: Maybe [Activity]
$sel:httpStatus:EnterStandbyResponse' :: EnterStandbyResponse -> Int
$sel:activities:EnterStandbyResponse' :: EnterStandbyResponse -> Maybe [Activity]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Activity]
activities
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus