{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.ScheduledUpdateGroupActionRequest
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.AutoScaling.Types.ScheduledUpdateGroupActionRequest where

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

-- | Describes information used for one or more scheduled scaling action
-- updates in a BatchPutScheduledUpdateGroupAction operation.
--
-- /See:/ 'newScheduledUpdateGroupActionRequest' smart constructor.
data ScheduledUpdateGroupActionRequest = ScheduledUpdateGroupActionRequest'
  { -- | The desired capacity is the initial capacity of the Auto Scaling group
    -- after the scheduled action runs and the capacity it attempts to
    -- maintain.
    ScheduledUpdateGroupActionRequest -> Maybe Int
desiredCapacity :: Prelude.Maybe Prelude.Int,
    -- | The date and time for the recurring schedule to end, in UTC.
    ScheduledUpdateGroupActionRequest -> Maybe ISO8601
endTime :: Prelude.Maybe Data.ISO8601,
    -- | The maximum size of the Auto Scaling group.
    ScheduledUpdateGroupActionRequest -> Maybe Int
maxSize :: Prelude.Maybe Prelude.Int,
    -- | The minimum size of the Auto Scaling group.
    ScheduledUpdateGroupActionRequest -> Maybe Int
minSize :: Prelude.Maybe Prelude.Int,
    -- | The recurring schedule for the action, in Unix cron syntax format. This
    -- format consists of five fields separated by white spaces: [Minute]
    -- [Hour] [Day_of_Month] [Month_of_Year] [Day_of_Week]. The value must be
    -- in quotes (for example, @\"30 0 1 1,6,12 *\"@). For more information
    -- about this format, see <http://crontab.org Crontab>.
    --
    -- When @StartTime@ and @EndTime@ are specified with @Recurrence@, they
    -- form the boundaries of when the recurring action starts and stops.
    --
    -- Cron expressions use Universal Coordinated Time (UTC) by default.
    ScheduledUpdateGroupActionRequest -> Maybe Text
recurrence :: Prelude.Maybe Prelude.Text,
    -- | The date and time for the action to start, in YYYY-MM-DDThh:mm:ssZ
    -- format in UTC\/GMT only and in quotes (for example,
    -- @\"2019-06-01T00:00:00Z\"@).
    --
    -- If you specify @Recurrence@ and @StartTime@, Amazon EC2 Auto Scaling
    -- performs the action at this time, and then performs the action based on
    -- the specified recurrence.
    --
    -- If you try to schedule the action in the past, Amazon EC2 Auto Scaling
    -- returns an error message.
    ScheduledUpdateGroupActionRequest -> Maybe ISO8601
startTime :: Prelude.Maybe Data.ISO8601,
    -- | Specifies the time zone for a cron expression. If a time zone is not
    -- provided, UTC is used by default.
    --
    -- Valid values are the canonical names of the IANA time zones, derived
    -- from the IANA Time Zone Database (such as @Etc\/GMT+9@ or
    -- @Pacific\/Tahiti@). For more information, see
    -- <https://en.wikipedia.org/wiki/List_of_tz_database_time_zones>.
    ScheduledUpdateGroupActionRequest -> Maybe Text
timeZone :: Prelude.Maybe Prelude.Text,
    -- | The name of the scaling action.
    ScheduledUpdateGroupActionRequest -> Text
scheduledActionName :: Prelude.Text
  }
  deriving (ScheduledUpdateGroupActionRequest
-> ScheduledUpdateGroupActionRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScheduledUpdateGroupActionRequest
-> ScheduledUpdateGroupActionRequest -> Bool
$c/= :: ScheduledUpdateGroupActionRequest
-> ScheduledUpdateGroupActionRequest -> Bool
== :: ScheduledUpdateGroupActionRequest
-> ScheduledUpdateGroupActionRequest -> Bool
$c== :: ScheduledUpdateGroupActionRequest
-> ScheduledUpdateGroupActionRequest -> Bool
Prelude.Eq, ReadPrec [ScheduledUpdateGroupActionRequest]
ReadPrec ScheduledUpdateGroupActionRequest
Int -> ReadS ScheduledUpdateGroupActionRequest
ReadS [ScheduledUpdateGroupActionRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ScheduledUpdateGroupActionRequest]
$creadListPrec :: ReadPrec [ScheduledUpdateGroupActionRequest]
readPrec :: ReadPrec ScheduledUpdateGroupActionRequest
$creadPrec :: ReadPrec ScheduledUpdateGroupActionRequest
readList :: ReadS [ScheduledUpdateGroupActionRequest]
$creadList :: ReadS [ScheduledUpdateGroupActionRequest]
readsPrec :: Int -> ReadS ScheduledUpdateGroupActionRequest
$creadsPrec :: Int -> ReadS ScheduledUpdateGroupActionRequest
Prelude.Read, Int -> ScheduledUpdateGroupActionRequest -> ShowS
[ScheduledUpdateGroupActionRequest] -> ShowS
ScheduledUpdateGroupActionRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScheduledUpdateGroupActionRequest] -> ShowS
$cshowList :: [ScheduledUpdateGroupActionRequest] -> ShowS
show :: ScheduledUpdateGroupActionRequest -> String
$cshow :: ScheduledUpdateGroupActionRequest -> String
showsPrec :: Int -> ScheduledUpdateGroupActionRequest -> ShowS
$cshowsPrec :: Int -> ScheduledUpdateGroupActionRequest -> ShowS
Prelude.Show, forall x.
Rep ScheduledUpdateGroupActionRequest x
-> ScheduledUpdateGroupActionRequest
forall x.
ScheduledUpdateGroupActionRequest
-> Rep ScheduledUpdateGroupActionRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ScheduledUpdateGroupActionRequest x
-> ScheduledUpdateGroupActionRequest
$cfrom :: forall x.
ScheduledUpdateGroupActionRequest
-> Rep ScheduledUpdateGroupActionRequest x
Prelude.Generic)

-- |
-- Create a value of 'ScheduledUpdateGroupActionRequest' 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:
--
-- 'desiredCapacity', 'scheduledUpdateGroupActionRequest_desiredCapacity' - The desired capacity is the initial capacity of the Auto Scaling group
-- after the scheduled action runs and the capacity it attempts to
-- maintain.
--
-- 'endTime', 'scheduledUpdateGroupActionRequest_endTime' - The date and time for the recurring schedule to end, in UTC.
--
-- 'maxSize', 'scheduledUpdateGroupActionRequest_maxSize' - The maximum size of the Auto Scaling group.
--
-- 'minSize', 'scheduledUpdateGroupActionRequest_minSize' - The minimum size of the Auto Scaling group.
--
-- 'recurrence', 'scheduledUpdateGroupActionRequest_recurrence' - The recurring schedule for the action, in Unix cron syntax format. This
-- format consists of five fields separated by white spaces: [Minute]
-- [Hour] [Day_of_Month] [Month_of_Year] [Day_of_Week]. The value must be
-- in quotes (for example, @\"30 0 1 1,6,12 *\"@). For more information
-- about this format, see <http://crontab.org Crontab>.
--
-- When @StartTime@ and @EndTime@ are specified with @Recurrence@, they
-- form the boundaries of when the recurring action starts and stops.
--
-- Cron expressions use Universal Coordinated Time (UTC) by default.
--
-- 'startTime', 'scheduledUpdateGroupActionRequest_startTime' - The date and time for the action to start, in YYYY-MM-DDThh:mm:ssZ
-- format in UTC\/GMT only and in quotes (for example,
-- @\"2019-06-01T00:00:00Z\"@).
--
-- If you specify @Recurrence@ and @StartTime@, Amazon EC2 Auto Scaling
-- performs the action at this time, and then performs the action based on
-- the specified recurrence.
--
-- If you try to schedule the action in the past, Amazon EC2 Auto Scaling
-- returns an error message.
--
-- 'timeZone', 'scheduledUpdateGroupActionRequest_timeZone' - Specifies the time zone for a cron expression. If a time zone is not
-- provided, UTC is used by default.
--
-- Valid values are the canonical names of the IANA time zones, derived
-- from the IANA Time Zone Database (such as @Etc\/GMT+9@ or
-- @Pacific\/Tahiti@). For more information, see
-- <https://en.wikipedia.org/wiki/List_of_tz_database_time_zones>.
--
-- 'scheduledActionName', 'scheduledUpdateGroupActionRequest_scheduledActionName' - The name of the scaling action.
newScheduledUpdateGroupActionRequest ::
  -- | 'scheduledActionName'
  Prelude.Text ->
  ScheduledUpdateGroupActionRequest
newScheduledUpdateGroupActionRequest :: Text -> ScheduledUpdateGroupActionRequest
newScheduledUpdateGroupActionRequest
  Text
pScheduledActionName_ =
    ScheduledUpdateGroupActionRequest'
      { $sel:desiredCapacity:ScheduledUpdateGroupActionRequest' :: Maybe Int
desiredCapacity =
          forall a. Maybe a
Prelude.Nothing,
        $sel:endTime:ScheduledUpdateGroupActionRequest' :: Maybe ISO8601
endTime = forall a. Maybe a
Prelude.Nothing,
        $sel:maxSize:ScheduledUpdateGroupActionRequest' :: Maybe Int
maxSize = forall a. Maybe a
Prelude.Nothing,
        $sel:minSize:ScheduledUpdateGroupActionRequest' :: Maybe Int
minSize = forall a. Maybe a
Prelude.Nothing,
        $sel:recurrence:ScheduledUpdateGroupActionRequest' :: Maybe Text
recurrence = forall a. Maybe a
Prelude.Nothing,
        $sel:startTime:ScheduledUpdateGroupActionRequest' :: Maybe ISO8601
startTime = forall a. Maybe a
Prelude.Nothing,
        $sel:timeZone:ScheduledUpdateGroupActionRequest' :: Maybe Text
timeZone = forall a. Maybe a
Prelude.Nothing,
        $sel:scheduledActionName:ScheduledUpdateGroupActionRequest' :: Text
scheduledActionName =
          Text
pScheduledActionName_
      }

-- | The desired capacity is the initial capacity of the Auto Scaling group
-- after the scheduled action runs and the capacity it attempts to
-- maintain.
scheduledUpdateGroupActionRequest_desiredCapacity :: Lens.Lens' ScheduledUpdateGroupActionRequest (Prelude.Maybe Prelude.Int)
scheduledUpdateGroupActionRequest_desiredCapacity :: Lens' ScheduledUpdateGroupActionRequest (Maybe Int)
scheduledUpdateGroupActionRequest_desiredCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledUpdateGroupActionRequest' {Maybe Int
desiredCapacity :: Maybe Int
$sel:desiredCapacity:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
desiredCapacity} -> Maybe Int
desiredCapacity) (\s :: ScheduledUpdateGroupActionRequest
s@ScheduledUpdateGroupActionRequest' {} Maybe Int
a -> ScheduledUpdateGroupActionRequest
s {$sel:desiredCapacity:ScheduledUpdateGroupActionRequest' :: Maybe Int
desiredCapacity = Maybe Int
a} :: ScheduledUpdateGroupActionRequest)

-- | The date and time for the recurring schedule to end, in UTC.
scheduledUpdateGroupActionRequest_endTime :: Lens.Lens' ScheduledUpdateGroupActionRequest (Prelude.Maybe Prelude.UTCTime)
scheduledUpdateGroupActionRequest_endTime :: Lens' ScheduledUpdateGroupActionRequest (Maybe UTCTime)
scheduledUpdateGroupActionRequest_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledUpdateGroupActionRequest' {Maybe ISO8601
endTime :: Maybe ISO8601
$sel:endTime:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe ISO8601
endTime} -> Maybe ISO8601
endTime) (\s :: ScheduledUpdateGroupActionRequest
s@ScheduledUpdateGroupActionRequest' {} Maybe ISO8601
a -> ScheduledUpdateGroupActionRequest
s {$sel:endTime:ScheduledUpdateGroupActionRequest' :: Maybe ISO8601
endTime = Maybe ISO8601
a} :: ScheduledUpdateGroupActionRequest) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The maximum size of the Auto Scaling group.
scheduledUpdateGroupActionRequest_maxSize :: Lens.Lens' ScheduledUpdateGroupActionRequest (Prelude.Maybe Prelude.Int)
scheduledUpdateGroupActionRequest_maxSize :: Lens' ScheduledUpdateGroupActionRequest (Maybe Int)
scheduledUpdateGroupActionRequest_maxSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledUpdateGroupActionRequest' {Maybe Int
maxSize :: Maybe Int
$sel:maxSize:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
maxSize} -> Maybe Int
maxSize) (\s :: ScheduledUpdateGroupActionRequest
s@ScheduledUpdateGroupActionRequest' {} Maybe Int
a -> ScheduledUpdateGroupActionRequest
s {$sel:maxSize:ScheduledUpdateGroupActionRequest' :: Maybe Int
maxSize = Maybe Int
a} :: ScheduledUpdateGroupActionRequest)

-- | The minimum size of the Auto Scaling group.
scheduledUpdateGroupActionRequest_minSize :: Lens.Lens' ScheduledUpdateGroupActionRequest (Prelude.Maybe Prelude.Int)
scheduledUpdateGroupActionRequest_minSize :: Lens' ScheduledUpdateGroupActionRequest (Maybe Int)
scheduledUpdateGroupActionRequest_minSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledUpdateGroupActionRequest' {Maybe Int
minSize :: Maybe Int
$sel:minSize:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
minSize} -> Maybe Int
minSize) (\s :: ScheduledUpdateGroupActionRequest
s@ScheduledUpdateGroupActionRequest' {} Maybe Int
a -> ScheduledUpdateGroupActionRequest
s {$sel:minSize:ScheduledUpdateGroupActionRequest' :: Maybe Int
minSize = Maybe Int
a} :: ScheduledUpdateGroupActionRequest)

-- | The recurring schedule for the action, in Unix cron syntax format. This
-- format consists of five fields separated by white spaces: [Minute]
-- [Hour] [Day_of_Month] [Month_of_Year] [Day_of_Week]. The value must be
-- in quotes (for example, @\"30 0 1 1,6,12 *\"@). For more information
-- about this format, see <http://crontab.org Crontab>.
--
-- When @StartTime@ and @EndTime@ are specified with @Recurrence@, they
-- form the boundaries of when the recurring action starts and stops.
--
-- Cron expressions use Universal Coordinated Time (UTC) by default.
scheduledUpdateGroupActionRequest_recurrence :: Lens.Lens' ScheduledUpdateGroupActionRequest (Prelude.Maybe Prelude.Text)
scheduledUpdateGroupActionRequest_recurrence :: Lens' ScheduledUpdateGroupActionRequest (Maybe Text)
scheduledUpdateGroupActionRequest_recurrence = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledUpdateGroupActionRequest' {Maybe Text
recurrence :: Maybe Text
$sel:recurrence:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Text
recurrence} -> Maybe Text
recurrence) (\s :: ScheduledUpdateGroupActionRequest
s@ScheduledUpdateGroupActionRequest' {} Maybe Text
a -> ScheduledUpdateGroupActionRequest
s {$sel:recurrence:ScheduledUpdateGroupActionRequest' :: Maybe Text
recurrence = Maybe Text
a} :: ScheduledUpdateGroupActionRequest)

-- | The date and time for the action to start, in YYYY-MM-DDThh:mm:ssZ
-- format in UTC\/GMT only and in quotes (for example,
-- @\"2019-06-01T00:00:00Z\"@).
--
-- If you specify @Recurrence@ and @StartTime@, Amazon EC2 Auto Scaling
-- performs the action at this time, and then performs the action based on
-- the specified recurrence.
--
-- If you try to schedule the action in the past, Amazon EC2 Auto Scaling
-- returns an error message.
scheduledUpdateGroupActionRequest_startTime :: Lens.Lens' ScheduledUpdateGroupActionRequest (Prelude.Maybe Prelude.UTCTime)
scheduledUpdateGroupActionRequest_startTime :: Lens' ScheduledUpdateGroupActionRequest (Maybe UTCTime)
scheduledUpdateGroupActionRequest_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledUpdateGroupActionRequest' {Maybe ISO8601
startTime :: Maybe ISO8601
$sel:startTime:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe ISO8601
startTime} -> Maybe ISO8601
startTime) (\s :: ScheduledUpdateGroupActionRequest
s@ScheduledUpdateGroupActionRequest' {} Maybe ISO8601
a -> ScheduledUpdateGroupActionRequest
s {$sel:startTime:ScheduledUpdateGroupActionRequest' :: Maybe ISO8601
startTime = Maybe ISO8601
a} :: ScheduledUpdateGroupActionRequest) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Specifies the time zone for a cron expression. If a time zone is not
-- provided, UTC is used by default.
--
-- Valid values are the canonical names of the IANA time zones, derived
-- from the IANA Time Zone Database (such as @Etc\/GMT+9@ or
-- @Pacific\/Tahiti@). For more information, see
-- <https://en.wikipedia.org/wiki/List_of_tz_database_time_zones>.
scheduledUpdateGroupActionRequest_timeZone :: Lens.Lens' ScheduledUpdateGroupActionRequest (Prelude.Maybe Prelude.Text)
scheduledUpdateGroupActionRequest_timeZone :: Lens' ScheduledUpdateGroupActionRequest (Maybe Text)
scheduledUpdateGroupActionRequest_timeZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledUpdateGroupActionRequest' {Maybe Text
timeZone :: Maybe Text
$sel:timeZone:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Text
timeZone} -> Maybe Text
timeZone) (\s :: ScheduledUpdateGroupActionRequest
s@ScheduledUpdateGroupActionRequest' {} Maybe Text
a -> ScheduledUpdateGroupActionRequest
s {$sel:timeZone:ScheduledUpdateGroupActionRequest' :: Maybe Text
timeZone = Maybe Text
a} :: ScheduledUpdateGroupActionRequest)

-- | The name of the scaling action.
scheduledUpdateGroupActionRequest_scheduledActionName :: Lens.Lens' ScheduledUpdateGroupActionRequest Prelude.Text
scheduledUpdateGroupActionRequest_scheduledActionName :: Lens' ScheduledUpdateGroupActionRequest Text
scheduledUpdateGroupActionRequest_scheduledActionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledUpdateGroupActionRequest' {Text
scheduledActionName :: Text
$sel:scheduledActionName:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Text
scheduledActionName} -> Text
scheduledActionName) (\s :: ScheduledUpdateGroupActionRequest
s@ScheduledUpdateGroupActionRequest' {} Text
a -> ScheduledUpdateGroupActionRequest
s {$sel:scheduledActionName:ScheduledUpdateGroupActionRequest' :: Text
scheduledActionName = Text
a} :: ScheduledUpdateGroupActionRequest)

instance
  Prelude.Hashable
    ScheduledUpdateGroupActionRequest
  where
  hashWithSalt :: Int -> ScheduledUpdateGroupActionRequest -> Int
hashWithSalt
    Int
_salt
    ScheduledUpdateGroupActionRequest' {Maybe Int
Maybe Text
Maybe ISO8601
Text
scheduledActionName :: Text
timeZone :: Maybe Text
startTime :: Maybe ISO8601
recurrence :: Maybe Text
minSize :: Maybe Int
maxSize :: Maybe Int
endTime :: Maybe ISO8601
desiredCapacity :: Maybe Int
$sel:scheduledActionName:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Text
$sel:timeZone:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Text
$sel:startTime:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe ISO8601
$sel:recurrence:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Text
$sel:minSize:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
$sel:maxSize:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
$sel:endTime:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe ISO8601
$sel:desiredCapacity:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
desiredCapacity
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
endTime
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxSize
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
minSize
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
recurrence
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
startTime
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
timeZone
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
scheduledActionName

instance
  Prelude.NFData
    ScheduledUpdateGroupActionRequest
  where
  rnf :: ScheduledUpdateGroupActionRequest -> ()
rnf ScheduledUpdateGroupActionRequest' {Maybe Int
Maybe Text
Maybe ISO8601
Text
scheduledActionName :: Text
timeZone :: Maybe Text
startTime :: Maybe ISO8601
recurrence :: Maybe Text
minSize :: Maybe Int
maxSize :: Maybe Int
endTime :: Maybe ISO8601
desiredCapacity :: Maybe Int
$sel:scheduledActionName:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Text
$sel:timeZone:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Text
$sel:startTime:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe ISO8601
$sel:recurrence:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Text
$sel:minSize:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
$sel:maxSize:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
$sel:endTime:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe ISO8601
$sel:desiredCapacity:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
desiredCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
minSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
recurrence
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
timeZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
scheduledActionName

instance
  Data.ToQuery
    ScheduledUpdateGroupActionRequest
  where
  toQuery :: ScheduledUpdateGroupActionRequest -> QueryString
toQuery ScheduledUpdateGroupActionRequest' {Maybe Int
Maybe Text
Maybe ISO8601
Text
scheduledActionName :: Text
timeZone :: Maybe Text
startTime :: Maybe ISO8601
recurrence :: Maybe Text
minSize :: Maybe Int
maxSize :: Maybe Int
endTime :: Maybe ISO8601
desiredCapacity :: Maybe Int
$sel:scheduledActionName:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Text
$sel:timeZone:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Text
$sel:startTime:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe ISO8601
$sel:recurrence:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Text
$sel:minSize:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
$sel:maxSize:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
$sel:endTime:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe ISO8601
$sel:desiredCapacity:ScheduledUpdateGroupActionRequest' :: ScheduledUpdateGroupActionRequest -> Maybe Int
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"DesiredCapacity" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
desiredCapacity,
        ByteString
"EndTime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
endTime,
        ByteString
"MaxSize" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxSize,
        ByteString
"MinSize" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
minSize,
        ByteString
"Recurrence" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
recurrence,
        ByteString
"StartTime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
startTime,
        ByteString
"TimeZone" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
timeZone,
        ByteString
"ScheduledActionName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
scheduledActionName
      ]