{-# 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.SuspendProcesses
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Suspends the specified auto scaling processes, or all processes, for the
-- specified Auto Scaling group.
--
-- If you suspend either the @Launch@ or @Terminate@ process types, it can
-- prevent other process types from functioning properly. For more
-- information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/as-suspend-resume-processes.html Suspending and resuming scaling processes>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- To resume processes that have been suspended, call the ResumeProcesses
-- API.
module Amazonka.AutoScaling.SuspendProcesses
  ( -- * Creating a Request
    SuspendProcesses (..),
    newSuspendProcesses,

    -- * Request Lenses
    suspendProcesses_scalingProcesses,
    suspendProcesses_autoScalingGroupName,

    -- * Destructuring the Response
    SuspendProcessesResponse (..),
    newSuspendProcessesResponse,
  )
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:/ 'newSuspendProcesses' smart constructor.
data SuspendProcesses = SuspendProcesses'
  { -- | One or more of the following processes:
    --
    -- -   @Launch@
    --
    -- -   @Terminate@
    --
    -- -   @AddToLoadBalancer@
    --
    -- -   @AlarmNotification@
    --
    -- -   @AZRebalance@
    --
    -- -   @HealthCheck@
    --
    -- -   @InstanceRefresh@
    --
    -- -   @ReplaceUnhealthy@
    --
    -- -   @ScheduledActions@
    --
    -- If you omit this property, all processes are specified.
    SuspendProcesses -> Maybe [Text]
scalingProcesses :: Prelude.Maybe [Prelude.Text],
    -- | The name of the Auto Scaling group.
    SuspendProcesses -> Text
autoScalingGroupName :: Prelude.Text
  }
  deriving (SuspendProcesses -> SuspendProcesses -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SuspendProcesses -> SuspendProcesses -> Bool
$c/= :: SuspendProcesses -> SuspendProcesses -> Bool
== :: SuspendProcesses -> SuspendProcesses -> Bool
$c== :: SuspendProcesses -> SuspendProcesses -> Bool
Prelude.Eq, ReadPrec [SuspendProcesses]
ReadPrec SuspendProcesses
Int -> ReadS SuspendProcesses
ReadS [SuspendProcesses]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SuspendProcesses]
$creadListPrec :: ReadPrec [SuspendProcesses]
readPrec :: ReadPrec SuspendProcesses
$creadPrec :: ReadPrec SuspendProcesses
readList :: ReadS [SuspendProcesses]
$creadList :: ReadS [SuspendProcesses]
readsPrec :: Int -> ReadS SuspendProcesses
$creadsPrec :: Int -> ReadS SuspendProcesses
Prelude.Read, Int -> SuspendProcesses -> ShowS
[SuspendProcesses] -> ShowS
SuspendProcesses -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SuspendProcesses] -> ShowS
$cshowList :: [SuspendProcesses] -> ShowS
show :: SuspendProcesses -> String
$cshow :: SuspendProcesses -> String
showsPrec :: Int -> SuspendProcesses -> ShowS
$cshowsPrec :: Int -> SuspendProcesses -> ShowS
Prelude.Show, forall x. Rep SuspendProcesses x -> SuspendProcesses
forall x. SuspendProcesses -> Rep SuspendProcesses x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SuspendProcesses x -> SuspendProcesses
$cfrom :: forall x. SuspendProcesses -> Rep SuspendProcesses x
Prelude.Generic)

-- |
-- Create a value of 'SuspendProcesses' 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:
--
-- 'scalingProcesses', 'suspendProcesses_scalingProcesses' - One or more of the following processes:
--
-- -   @Launch@
--
-- -   @Terminate@
--
-- -   @AddToLoadBalancer@
--
-- -   @AlarmNotification@
--
-- -   @AZRebalance@
--
-- -   @HealthCheck@
--
-- -   @InstanceRefresh@
--
-- -   @ReplaceUnhealthy@
--
-- -   @ScheduledActions@
--
-- If you omit this property, all processes are specified.
--
-- 'autoScalingGroupName', 'suspendProcesses_autoScalingGroupName' - The name of the Auto Scaling group.
newSuspendProcesses ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  SuspendProcesses
newSuspendProcesses :: Text -> SuspendProcesses
newSuspendProcesses Text
pAutoScalingGroupName_ =
  SuspendProcesses'
    { $sel:scalingProcesses:SuspendProcesses' :: Maybe [Text]
scalingProcesses =
        forall a. Maybe a
Prelude.Nothing,
      $sel:autoScalingGroupName:SuspendProcesses' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_
    }

-- | One or more of the following processes:
--
-- -   @Launch@
--
-- -   @Terminate@
--
-- -   @AddToLoadBalancer@
--
-- -   @AlarmNotification@
--
-- -   @AZRebalance@
--
-- -   @HealthCheck@
--
-- -   @InstanceRefresh@
--
-- -   @ReplaceUnhealthy@
--
-- -   @ScheduledActions@
--
-- If you omit this property, all processes are specified.
suspendProcesses_scalingProcesses :: Lens.Lens' SuspendProcesses (Prelude.Maybe [Prelude.Text])
suspendProcesses_scalingProcesses :: Lens' SuspendProcesses (Maybe [Text])
suspendProcesses_scalingProcesses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SuspendProcesses' {Maybe [Text]
scalingProcesses :: Maybe [Text]
$sel:scalingProcesses:SuspendProcesses' :: SuspendProcesses -> Maybe [Text]
scalingProcesses} -> Maybe [Text]
scalingProcesses) (\s :: SuspendProcesses
s@SuspendProcesses' {} Maybe [Text]
a -> SuspendProcesses
s {$sel:scalingProcesses:SuspendProcesses' :: Maybe [Text]
scalingProcesses = Maybe [Text]
a} :: SuspendProcesses) 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.
suspendProcesses_autoScalingGroupName :: Lens.Lens' SuspendProcesses Prelude.Text
suspendProcesses_autoScalingGroupName :: Lens' SuspendProcesses Text
suspendProcesses_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SuspendProcesses' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:SuspendProcesses' :: SuspendProcesses -> Text
autoScalingGroupName} -> Text
autoScalingGroupName) (\s :: SuspendProcesses
s@SuspendProcesses' {} Text
a -> SuspendProcesses
s {$sel:autoScalingGroupName:SuspendProcesses' :: Text
autoScalingGroupName = Text
a} :: SuspendProcesses)

instance Core.AWSRequest SuspendProcesses where
  type
    AWSResponse SuspendProcesses =
      SuspendProcessesResponse
  request :: (Service -> Service)
-> SuspendProcesses -> Request SuspendProcesses
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 SuspendProcesses
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse SuspendProcesses)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull SuspendProcessesResponse
SuspendProcessesResponse'

instance Prelude.Hashable SuspendProcesses where
  hashWithSalt :: Int -> SuspendProcesses -> Int
hashWithSalt Int
_salt SuspendProcesses' {Maybe [Text]
Text
autoScalingGroupName :: Text
scalingProcesses :: Maybe [Text]
$sel:autoScalingGroupName:SuspendProcesses' :: SuspendProcesses -> Text
$sel:scalingProcesses:SuspendProcesses' :: SuspendProcesses -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
scalingProcesses
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName

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

instance Data.ToHeaders SuspendProcesses where
  toHeaders :: SuspendProcesses -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery SuspendProcesses where
  toQuery :: SuspendProcesses -> QueryString
toQuery SuspendProcesses' {Maybe [Text]
Text
autoScalingGroupName :: Text
scalingProcesses :: Maybe [Text]
$sel:autoScalingGroupName:SuspendProcesses' :: SuspendProcesses -> Text
$sel:scalingProcesses:SuspendProcesses' :: SuspendProcesses -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"SuspendProcesses" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-01-01" :: Prelude.ByteString),
        ByteString
"ScalingProcesses"
          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]
scalingProcesses
            ),
        ByteString
"AutoScalingGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
autoScalingGroupName
      ]

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

-- |
-- Create a value of 'SuspendProcessesResponse' 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.
newSuspendProcessesResponse ::
  SuspendProcessesResponse
newSuspendProcessesResponse :: SuspendProcessesResponse
newSuspendProcessesResponse =
  SuspendProcessesResponse
SuspendProcessesResponse'

instance Prelude.NFData SuspendProcessesResponse where
  rnf :: SuspendProcessesResponse -> ()
rnf SuspendProcessesResponse
_ = ()