{-# 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.ExitStandby
-- 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 out of the standby state.
--
-- After you put the instances back in service, the desired capacity is
-- incremented.
--
-- 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.ExitStandby
  ( -- * Creating a Request
    ExitStandby (..),
    newExitStandby,

    -- * Request Lenses
    exitStandby_instanceIds,
    exitStandby_autoScalingGroupName,

    -- * Destructuring the Response
    ExitStandbyResponse (..),
    newExitStandbyResponse,

    -- * Response Lenses
    exitStandbyResponse_activities,
    exitStandbyResponse_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:/ 'newExitStandby' smart constructor.
data ExitStandby = ExitStandby'
  { -- | The IDs of the instances. You can specify up to 20 instances.
    ExitStandby -> Maybe [Text]
instanceIds :: Prelude.Maybe [Prelude.Text],
    -- | The name of the Auto Scaling group.
    ExitStandby -> Text
autoScalingGroupName :: Prelude.Text
  }
  deriving (ExitStandby -> ExitStandby -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExitStandby -> ExitStandby -> Bool
$c/= :: ExitStandby -> ExitStandby -> Bool
== :: ExitStandby -> ExitStandby -> Bool
$c== :: ExitStandby -> ExitStandby -> Bool
Prelude.Eq, ReadPrec [ExitStandby]
ReadPrec ExitStandby
Int -> ReadS ExitStandby
ReadS [ExitStandby]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExitStandby]
$creadListPrec :: ReadPrec [ExitStandby]
readPrec :: ReadPrec ExitStandby
$creadPrec :: ReadPrec ExitStandby
readList :: ReadS [ExitStandby]
$creadList :: ReadS [ExitStandby]
readsPrec :: Int -> ReadS ExitStandby
$creadsPrec :: Int -> ReadS ExitStandby
Prelude.Read, Int -> ExitStandby -> ShowS
[ExitStandby] -> ShowS
ExitStandby -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExitStandby] -> ShowS
$cshowList :: [ExitStandby] -> ShowS
show :: ExitStandby -> String
$cshow :: ExitStandby -> String
showsPrec :: Int -> ExitStandby -> ShowS
$cshowsPrec :: Int -> ExitStandby -> ShowS
Prelude.Show, forall x. Rep ExitStandby x -> ExitStandby
forall x. ExitStandby -> Rep ExitStandby x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExitStandby x -> ExitStandby
$cfrom :: forall x. ExitStandby -> Rep ExitStandby x
Prelude.Generic)

-- |
-- Create a value of 'ExitStandby' 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', 'exitStandby_instanceIds' - The IDs of the instances. You can specify up to 20 instances.
--
-- 'autoScalingGroupName', 'exitStandby_autoScalingGroupName' - The name of the Auto Scaling group.
newExitStandby ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  ExitStandby
newExitStandby :: Text -> ExitStandby
newExitStandby Text
pAutoScalingGroupName_ =
  ExitStandby'
    { $sel:instanceIds:ExitStandby' :: Maybe [Text]
instanceIds = forall a. Maybe a
Prelude.Nothing,
      $sel:autoScalingGroupName:ExitStandby' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_
    }

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

instance Core.AWSRequest ExitStandby where
  type AWSResponse ExitStandby = ExitStandbyResponse
  request :: (Service -> Service) -> ExitStandby -> Request ExitStandby
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 ExitStandby
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ExitStandby)))
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
"ExitStandbyResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [Activity] -> Int -> ExitStandbyResponse
ExitStandbyResponse'
            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 ExitStandby where
  hashWithSalt :: Int -> ExitStandby -> Int
hashWithSalt Int
_salt ExitStandby' {Maybe [Text]
Text
autoScalingGroupName :: Text
instanceIds :: Maybe [Text]
$sel:autoScalingGroupName:ExitStandby' :: ExitStandby -> Text
$sel:instanceIds:ExitStandby' :: ExitStandby -> 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

instance Prelude.NFData ExitStandby where
  rnf :: ExitStandby -> ()
rnf ExitStandby' {Maybe [Text]
Text
autoScalingGroupName :: Text
instanceIds :: Maybe [Text]
$sel:autoScalingGroupName:ExitStandby' :: ExitStandby -> Text
$sel:instanceIds:ExitStandby' :: ExitStandby -> 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

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

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

instance Data.ToQuery ExitStandby where
  toQuery :: ExitStandby -> QueryString
toQuery ExitStandby' {Maybe [Text]
Text
autoScalingGroupName :: Text
instanceIds :: Maybe [Text]
$sel:autoScalingGroupName:ExitStandby' :: ExitStandby -> Text
$sel:instanceIds:ExitStandby' :: ExitStandby -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ExitStandby" :: 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
      ]

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

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

-- | The activities related to moving instances out of @Standby@ mode.
exitStandbyResponse_activities :: Lens.Lens' ExitStandbyResponse (Prelude.Maybe [Activity])
exitStandbyResponse_activities :: Lens' ExitStandbyResponse (Maybe [Activity])
exitStandbyResponse_activities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExitStandbyResponse' {Maybe [Activity]
activities :: Maybe [Activity]
$sel:activities:ExitStandbyResponse' :: ExitStandbyResponse -> Maybe [Activity]
activities} -> Maybe [Activity]
activities) (\s :: ExitStandbyResponse
s@ExitStandbyResponse' {} Maybe [Activity]
a -> ExitStandbyResponse
s {$sel:activities:ExitStandbyResponse' :: Maybe [Activity]
activities = Maybe [Activity]
a} :: ExitStandbyResponse) 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.
exitStandbyResponse_httpStatus :: Lens.Lens' ExitStandbyResponse Prelude.Int
exitStandbyResponse_httpStatus :: Lens' ExitStandbyResponse Int
exitStandbyResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExitStandbyResponse' {Int
httpStatus :: Int
$sel:httpStatus:ExitStandbyResponse' :: ExitStandbyResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ExitStandbyResponse
s@ExitStandbyResponse' {} Int
a -> ExitStandbyResponse
s {$sel:httpStatus:ExitStandbyResponse' :: Int
httpStatus = Int
a} :: ExitStandbyResponse)

instance Prelude.NFData ExitStandbyResponse where
  rnf :: ExitStandbyResponse -> ()
rnf ExitStandbyResponse' {Int
Maybe [Activity]
httpStatus :: Int
activities :: Maybe [Activity]
$sel:httpStatus:ExitStandbyResponse' :: ExitStandbyResponse -> Int
$sel:activities:ExitStandbyResponse' :: ExitStandbyResponse -> 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