{-# 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.SetInstanceProtection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the instance protection settings of the specified instances.
-- This operation cannot be called on instances in a warm pool.
--
-- For more information about preventing instances that are part of an Auto
-- Scaling group from terminating on scale in, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ec2-auto-scaling-instance-protection.html Using instance scale-in protection>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- If you exceed your maximum limit of instance IDs, which is 50 per Auto
-- Scaling group, the call fails.
module Amazonka.AutoScaling.SetInstanceProtection
  ( -- * Creating a Request
    SetInstanceProtection (..),
    newSetInstanceProtection,

    -- * Request Lenses
    setInstanceProtection_instanceIds,
    setInstanceProtection_autoScalingGroupName,
    setInstanceProtection_protectedFromScaleIn,

    -- * Destructuring the Response
    SetInstanceProtectionResponse (..),
    newSetInstanceProtectionResponse,

    -- * Response Lenses
    setInstanceProtectionResponse_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:/ 'newSetInstanceProtection' smart constructor.
data SetInstanceProtection = SetInstanceProtection'
  { -- | One or more instance IDs. You can specify up to 50 instances.
    SetInstanceProtection -> [Text]
instanceIds :: [Prelude.Text],
    -- | The name of the Auto Scaling group.
    SetInstanceProtection -> Text
autoScalingGroupName :: Prelude.Text,
    -- | Indicates whether the instance is protected from termination by Amazon
    -- EC2 Auto Scaling when scaling in.
    SetInstanceProtection -> Bool
protectedFromScaleIn :: Prelude.Bool
  }
  deriving (SetInstanceProtection -> SetInstanceProtection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetInstanceProtection -> SetInstanceProtection -> Bool
$c/= :: SetInstanceProtection -> SetInstanceProtection -> Bool
== :: SetInstanceProtection -> SetInstanceProtection -> Bool
$c== :: SetInstanceProtection -> SetInstanceProtection -> Bool
Prelude.Eq, ReadPrec [SetInstanceProtection]
ReadPrec SetInstanceProtection
Int -> ReadS SetInstanceProtection
ReadS [SetInstanceProtection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SetInstanceProtection]
$creadListPrec :: ReadPrec [SetInstanceProtection]
readPrec :: ReadPrec SetInstanceProtection
$creadPrec :: ReadPrec SetInstanceProtection
readList :: ReadS [SetInstanceProtection]
$creadList :: ReadS [SetInstanceProtection]
readsPrec :: Int -> ReadS SetInstanceProtection
$creadsPrec :: Int -> ReadS SetInstanceProtection
Prelude.Read, Int -> SetInstanceProtection -> ShowS
[SetInstanceProtection] -> ShowS
SetInstanceProtection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetInstanceProtection] -> ShowS
$cshowList :: [SetInstanceProtection] -> ShowS
show :: SetInstanceProtection -> String
$cshow :: SetInstanceProtection -> String
showsPrec :: Int -> SetInstanceProtection -> ShowS
$cshowsPrec :: Int -> SetInstanceProtection -> ShowS
Prelude.Show, forall x. Rep SetInstanceProtection x -> SetInstanceProtection
forall x. SetInstanceProtection -> Rep SetInstanceProtection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetInstanceProtection x -> SetInstanceProtection
$cfrom :: forall x. SetInstanceProtection -> Rep SetInstanceProtection x
Prelude.Generic)

-- |
-- Create a value of 'SetInstanceProtection' 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', 'setInstanceProtection_instanceIds' - One or more instance IDs. You can specify up to 50 instances.
--
-- 'autoScalingGroupName', 'setInstanceProtection_autoScalingGroupName' - The name of the Auto Scaling group.
--
-- 'protectedFromScaleIn', 'setInstanceProtection_protectedFromScaleIn' - Indicates whether the instance is protected from termination by Amazon
-- EC2 Auto Scaling when scaling in.
newSetInstanceProtection ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  -- | 'protectedFromScaleIn'
  Prelude.Bool ->
  SetInstanceProtection
newSetInstanceProtection :: Text -> Bool -> SetInstanceProtection
newSetInstanceProtection
  Text
pAutoScalingGroupName_
  Bool
pProtectedFromScaleIn_ =
    SetInstanceProtection'
      { $sel:instanceIds:SetInstanceProtection' :: [Text]
instanceIds =
          forall a. Monoid a => a
Prelude.mempty,
        $sel:autoScalingGroupName:SetInstanceProtection' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_,
        $sel:protectedFromScaleIn:SetInstanceProtection' :: Bool
protectedFromScaleIn = Bool
pProtectedFromScaleIn_
      }

-- | One or more instance IDs. You can specify up to 50 instances.
setInstanceProtection_instanceIds :: Lens.Lens' SetInstanceProtection [Prelude.Text]
setInstanceProtection_instanceIds :: Lens' SetInstanceProtection [Text]
setInstanceProtection_instanceIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetInstanceProtection' {[Text]
instanceIds :: [Text]
$sel:instanceIds:SetInstanceProtection' :: SetInstanceProtection -> [Text]
instanceIds} -> [Text]
instanceIds) (\s :: SetInstanceProtection
s@SetInstanceProtection' {} [Text]
a -> SetInstanceProtection
s {$sel:instanceIds:SetInstanceProtection' :: [Text]
instanceIds = [Text]
a} :: SetInstanceProtection) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. 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.
setInstanceProtection_autoScalingGroupName :: Lens.Lens' SetInstanceProtection Prelude.Text
setInstanceProtection_autoScalingGroupName :: Lens' SetInstanceProtection Text
setInstanceProtection_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetInstanceProtection' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:SetInstanceProtection' :: SetInstanceProtection -> Text
autoScalingGroupName} -> Text
autoScalingGroupName) (\s :: SetInstanceProtection
s@SetInstanceProtection' {} Text
a -> SetInstanceProtection
s {$sel:autoScalingGroupName:SetInstanceProtection' :: Text
autoScalingGroupName = Text
a} :: SetInstanceProtection)

-- | Indicates whether the instance is protected from termination by Amazon
-- EC2 Auto Scaling when scaling in.
setInstanceProtection_protectedFromScaleIn :: Lens.Lens' SetInstanceProtection Prelude.Bool
setInstanceProtection_protectedFromScaleIn :: Lens' SetInstanceProtection Bool
setInstanceProtection_protectedFromScaleIn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetInstanceProtection' {Bool
protectedFromScaleIn :: Bool
$sel:protectedFromScaleIn:SetInstanceProtection' :: SetInstanceProtection -> Bool
protectedFromScaleIn} -> Bool
protectedFromScaleIn) (\s :: SetInstanceProtection
s@SetInstanceProtection' {} Bool
a -> SetInstanceProtection
s {$sel:protectedFromScaleIn:SetInstanceProtection' :: Bool
protectedFromScaleIn = Bool
a} :: SetInstanceProtection)

instance Core.AWSRequest SetInstanceProtection where
  type
    AWSResponse SetInstanceProtection =
      SetInstanceProtectionResponse
  request :: (Service -> Service)
-> SetInstanceProtection -> Request SetInstanceProtection
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 SetInstanceProtection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SetInstanceProtection)))
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
"SetInstanceProtectionResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> SetInstanceProtectionResponse
SetInstanceProtectionResponse'
            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 SetInstanceProtection where
  hashWithSalt :: Int -> SetInstanceProtection -> Int
hashWithSalt Int
_salt SetInstanceProtection' {Bool
[Text]
Text
protectedFromScaleIn :: Bool
autoScalingGroupName :: Text
instanceIds :: [Text]
$sel:protectedFromScaleIn:SetInstanceProtection' :: SetInstanceProtection -> Bool
$sel:autoScalingGroupName:SetInstanceProtection' :: SetInstanceProtection -> Text
$sel:instanceIds:SetInstanceProtection' :: SetInstanceProtection -> [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
instanceIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Bool
protectedFromScaleIn

instance Prelude.NFData SetInstanceProtection where
  rnf :: SetInstanceProtection -> ()
rnf SetInstanceProtection' {Bool
[Text]
Text
protectedFromScaleIn :: Bool
autoScalingGroupName :: Text
instanceIds :: [Text]
$sel:protectedFromScaleIn:SetInstanceProtection' :: SetInstanceProtection -> Bool
$sel:autoScalingGroupName:SetInstanceProtection' :: SetInstanceProtection -> Text
$sel:instanceIds:SetInstanceProtection' :: SetInstanceProtection -> [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf [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
protectedFromScaleIn

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

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

instance Data.ToQuery SetInstanceProtection where
  toQuery :: SetInstanceProtection -> QueryString
toQuery SetInstanceProtection' {Bool
[Text]
Text
protectedFromScaleIn :: Bool
autoScalingGroupName :: Text
instanceIds :: [Text]
$sel:protectedFromScaleIn:SetInstanceProtection' :: SetInstanceProtection -> Bool
$sel:autoScalingGroupName:SetInstanceProtection' :: SetInstanceProtection -> Text
$sel:instanceIds:SetInstanceProtection' :: SetInstanceProtection -> [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"SetInstanceProtection" :: 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.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Text]
instanceIds,
        ByteString
"AutoScalingGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
autoScalingGroupName,
        ByteString
"ProtectedFromScaleIn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Bool
protectedFromScaleIn
      ]

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

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

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

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