{-# 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.Redshift.ModifyScheduledAction
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies a scheduled action.
module Amazonka.Redshift.ModifyScheduledAction
  ( -- * Creating a Request
    ModifyScheduledAction (..),
    newModifyScheduledAction,

    -- * Request Lenses
    modifyScheduledAction_enable,
    modifyScheduledAction_endTime,
    modifyScheduledAction_iamRole,
    modifyScheduledAction_schedule,
    modifyScheduledAction_scheduledActionDescription,
    modifyScheduledAction_startTime,
    modifyScheduledAction_targetAction,
    modifyScheduledAction_scheduledActionName,

    -- * Destructuring the Response
    ScheduledAction (..),
    newScheduledAction,

    -- * Response Lenses
    scheduledAction_endTime,
    scheduledAction_iamRole,
    scheduledAction_nextInvocations,
    scheduledAction_schedule,
    scheduledAction_scheduledActionDescription,
    scheduledAction_scheduledActionName,
    scheduledAction_startTime,
    scheduledAction_state,
    scheduledAction_targetAction,
  )
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
import Amazonka.Redshift.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newModifyScheduledAction' smart constructor.
data ModifyScheduledAction = ModifyScheduledAction'
  { -- | A modified enable flag of the scheduled action. If true, the scheduled
    -- action is active. If false, the scheduled action is disabled.
    ModifyScheduledAction -> Maybe Bool
enable :: Prelude.Maybe Prelude.Bool,
    -- | A modified end time of the scheduled action. For more information about
    -- this parameter, see ScheduledAction.
    ModifyScheduledAction -> Maybe ISO8601
endTime :: Prelude.Maybe Data.ISO8601,
    -- | A different IAM role to assume to run the target action. For more
    -- information about this parameter, see ScheduledAction.
    ModifyScheduledAction -> Maybe Text
iamRole :: Prelude.Maybe Prelude.Text,
    -- | A modified schedule in either @at( )@ or @cron( )@ format. For more
    -- information about this parameter, see ScheduledAction.
    ModifyScheduledAction -> Maybe Text
schedule :: Prelude.Maybe Prelude.Text,
    -- | A modified description of the scheduled action.
    ModifyScheduledAction -> Maybe Text
scheduledActionDescription :: Prelude.Maybe Prelude.Text,
    -- | A modified start time of the scheduled action. For more information
    -- about this parameter, see ScheduledAction.
    ModifyScheduledAction -> Maybe ISO8601
startTime :: Prelude.Maybe Data.ISO8601,
    -- | A modified JSON format of the scheduled action. For more information
    -- about this parameter, see ScheduledAction.
    ModifyScheduledAction -> Maybe ScheduledActionType
targetAction :: Prelude.Maybe ScheduledActionType,
    -- | The name of the scheduled action to modify.
    ModifyScheduledAction -> Text
scheduledActionName :: Prelude.Text
  }
  deriving (ModifyScheduledAction -> ModifyScheduledAction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyScheduledAction -> ModifyScheduledAction -> Bool
$c/= :: ModifyScheduledAction -> ModifyScheduledAction -> Bool
== :: ModifyScheduledAction -> ModifyScheduledAction -> Bool
$c== :: ModifyScheduledAction -> ModifyScheduledAction -> Bool
Prelude.Eq, ReadPrec [ModifyScheduledAction]
ReadPrec ModifyScheduledAction
Int -> ReadS ModifyScheduledAction
ReadS [ModifyScheduledAction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyScheduledAction]
$creadListPrec :: ReadPrec [ModifyScheduledAction]
readPrec :: ReadPrec ModifyScheduledAction
$creadPrec :: ReadPrec ModifyScheduledAction
readList :: ReadS [ModifyScheduledAction]
$creadList :: ReadS [ModifyScheduledAction]
readsPrec :: Int -> ReadS ModifyScheduledAction
$creadsPrec :: Int -> ReadS ModifyScheduledAction
Prelude.Read, Int -> ModifyScheduledAction -> ShowS
[ModifyScheduledAction] -> ShowS
ModifyScheduledAction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyScheduledAction] -> ShowS
$cshowList :: [ModifyScheduledAction] -> ShowS
show :: ModifyScheduledAction -> String
$cshow :: ModifyScheduledAction -> String
showsPrec :: Int -> ModifyScheduledAction -> ShowS
$cshowsPrec :: Int -> ModifyScheduledAction -> ShowS
Prelude.Show, forall x. Rep ModifyScheduledAction x -> ModifyScheduledAction
forall x. ModifyScheduledAction -> Rep ModifyScheduledAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModifyScheduledAction x -> ModifyScheduledAction
$cfrom :: forall x. ModifyScheduledAction -> Rep ModifyScheduledAction x
Prelude.Generic)

-- |
-- Create a value of 'ModifyScheduledAction' 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:
--
-- 'enable', 'modifyScheduledAction_enable' - A modified enable flag of the scheduled action. If true, the scheduled
-- action is active. If false, the scheduled action is disabled.
--
-- 'endTime', 'modifyScheduledAction_endTime' - A modified end time of the scheduled action. For more information about
-- this parameter, see ScheduledAction.
--
-- 'iamRole', 'modifyScheduledAction_iamRole' - A different IAM role to assume to run the target action. For more
-- information about this parameter, see ScheduledAction.
--
-- 'schedule', 'modifyScheduledAction_schedule' - A modified schedule in either @at( )@ or @cron( )@ format. For more
-- information about this parameter, see ScheduledAction.
--
-- 'scheduledActionDescription', 'modifyScheduledAction_scheduledActionDescription' - A modified description of the scheduled action.
--
-- 'startTime', 'modifyScheduledAction_startTime' - A modified start time of the scheduled action. For more information
-- about this parameter, see ScheduledAction.
--
-- 'targetAction', 'modifyScheduledAction_targetAction' - A modified JSON format of the scheduled action. For more information
-- about this parameter, see ScheduledAction.
--
-- 'scheduledActionName', 'modifyScheduledAction_scheduledActionName' - The name of the scheduled action to modify.
newModifyScheduledAction ::
  -- | 'scheduledActionName'
  Prelude.Text ->
  ModifyScheduledAction
newModifyScheduledAction :: Text -> ModifyScheduledAction
newModifyScheduledAction Text
pScheduledActionName_ =
  ModifyScheduledAction'
    { $sel:enable:ModifyScheduledAction' :: Maybe Bool
enable = forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:ModifyScheduledAction' :: Maybe ISO8601
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:iamRole:ModifyScheduledAction' :: Maybe Text
iamRole = forall a. Maybe a
Prelude.Nothing,
      $sel:schedule:ModifyScheduledAction' :: Maybe Text
schedule = forall a. Maybe a
Prelude.Nothing,
      $sel:scheduledActionDescription:ModifyScheduledAction' :: Maybe Text
scheduledActionDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:ModifyScheduledAction' :: Maybe ISO8601
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:targetAction:ModifyScheduledAction' :: Maybe ScheduledActionType
targetAction = forall a. Maybe a
Prelude.Nothing,
      $sel:scheduledActionName:ModifyScheduledAction' :: Text
scheduledActionName = Text
pScheduledActionName_
    }

-- | A modified enable flag of the scheduled action. If true, the scheduled
-- action is active. If false, the scheduled action is disabled.
modifyScheduledAction_enable :: Lens.Lens' ModifyScheduledAction (Prelude.Maybe Prelude.Bool)
modifyScheduledAction_enable :: Lens' ModifyScheduledAction (Maybe Bool)
modifyScheduledAction_enable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyScheduledAction' {Maybe Bool
enable :: Maybe Bool
$sel:enable:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Bool
enable} -> Maybe Bool
enable) (\s :: ModifyScheduledAction
s@ModifyScheduledAction' {} Maybe Bool
a -> ModifyScheduledAction
s {$sel:enable:ModifyScheduledAction' :: Maybe Bool
enable = Maybe Bool
a} :: ModifyScheduledAction)

-- | A modified end time of the scheduled action. For more information about
-- this parameter, see ScheduledAction.
modifyScheduledAction_endTime :: Lens.Lens' ModifyScheduledAction (Prelude.Maybe Prelude.UTCTime)
modifyScheduledAction_endTime :: Lens' ModifyScheduledAction (Maybe UTCTime)
modifyScheduledAction_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyScheduledAction' {Maybe ISO8601
endTime :: Maybe ISO8601
$sel:endTime:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ISO8601
endTime} -> Maybe ISO8601
endTime) (\s :: ModifyScheduledAction
s@ModifyScheduledAction' {} Maybe ISO8601
a -> ModifyScheduledAction
s {$sel:endTime:ModifyScheduledAction' :: Maybe ISO8601
endTime = Maybe ISO8601
a} :: ModifyScheduledAction) 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

-- | A different IAM role to assume to run the target action. For more
-- information about this parameter, see ScheduledAction.
modifyScheduledAction_iamRole :: Lens.Lens' ModifyScheduledAction (Prelude.Maybe Prelude.Text)
modifyScheduledAction_iamRole :: Lens' ModifyScheduledAction (Maybe Text)
modifyScheduledAction_iamRole = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyScheduledAction' {Maybe Text
iamRole :: Maybe Text
$sel:iamRole:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
iamRole} -> Maybe Text
iamRole) (\s :: ModifyScheduledAction
s@ModifyScheduledAction' {} Maybe Text
a -> ModifyScheduledAction
s {$sel:iamRole:ModifyScheduledAction' :: Maybe Text
iamRole = Maybe Text
a} :: ModifyScheduledAction)

-- | A modified schedule in either @at( )@ or @cron( )@ format. For more
-- information about this parameter, see ScheduledAction.
modifyScheduledAction_schedule :: Lens.Lens' ModifyScheduledAction (Prelude.Maybe Prelude.Text)
modifyScheduledAction_schedule :: Lens' ModifyScheduledAction (Maybe Text)
modifyScheduledAction_schedule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyScheduledAction' {Maybe Text
schedule :: Maybe Text
$sel:schedule:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
schedule} -> Maybe Text
schedule) (\s :: ModifyScheduledAction
s@ModifyScheduledAction' {} Maybe Text
a -> ModifyScheduledAction
s {$sel:schedule:ModifyScheduledAction' :: Maybe Text
schedule = Maybe Text
a} :: ModifyScheduledAction)

-- | A modified description of the scheduled action.
modifyScheduledAction_scheduledActionDescription :: Lens.Lens' ModifyScheduledAction (Prelude.Maybe Prelude.Text)
modifyScheduledAction_scheduledActionDescription :: Lens' ModifyScheduledAction (Maybe Text)
modifyScheduledAction_scheduledActionDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyScheduledAction' {Maybe Text
scheduledActionDescription :: Maybe Text
$sel:scheduledActionDescription:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
scheduledActionDescription} -> Maybe Text
scheduledActionDescription) (\s :: ModifyScheduledAction
s@ModifyScheduledAction' {} Maybe Text
a -> ModifyScheduledAction
s {$sel:scheduledActionDescription:ModifyScheduledAction' :: Maybe Text
scheduledActionDescription = Maybe Text
a} :: ModifyScheduledAction)

-- | A modified start time of the scheduled action. For more information
-- about this parameter, see ScheduledAction.
modifyScheduledAction_startTime :: Lens.Lens' ModifyScheduledAction (Prelude.Maybe Prelude.UTCTime)
modifyScheduledAction_startTime :: Lens' ModifyScheduledAction (Maybe UTCTime)
modifyScheduledAction_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyScheduledAction' {Maybe ISO8601
startTime :: Maybe ISO8601
$sel:startTime:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ISO8601
startTime} -> Maybe ISO8601
startTime) (\s :: ModifyScheduledAction
s@ModifyScheduledAction' {} Maybe ISO8601
a -> ModifyScheduledAction
s {$sel:startTime:ModifyScheduledAction' :: Maybe ISO8601
startTime = Maybe ISO8601
a} :: ModifyScheduledAction) 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

-- | A modified JSON format of the scheduled action. For more information
-- about this parameter, see ScheduledAction.
modifyScheduledAction_targetAction :: Lens.Lens' ModifyScheduledAction (Prelude.Maybe ScheduledActionType)
modifyScheduledAction_targetAction :: Lens' ModifyScheduledAction (Maybe ScheduledActionType)
modifyScheduledAction_targetAction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyScheduledAction' {Maybe ScheduledActionType
targetAction :: Maybe ScheduledActionType
$sel:targetAction:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ScheduledActionType
targetAction} -> Maybe ScheduledActionType
targetAction) (\s :: ModifyScheduledAction
s@ModifyScheduledAction' {} Maybe ScheduledActionType
a -> ModifyScheduledAction
s {$sel:targetAction:ModifyScheduledAction' :: Maybe ScheduledActionType
targetAction = Maybe ScheduledActionType
a} :: ModifyScheduledAction)

-- | The name of the scheduled action to modify.
modifyScheduledAction_scheduledActionName :: Lens.Lens' ModifyScheduledAction Prelude.Text
modifyScheduledAction_scheduledActionName :: Lens' ModifyScheduledAction Text
modifyScheduledAction_scheduledActionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyScheduledAction' {Text
scheduledActionName :: Text
$sel:scheduledActionName:ModifyScheduledAction' :: ModifyScheduledAction -> Text
scheduledActionName} -> Text
scheduledActionName) (\s :: ModifyScheduledAction
s@ModifyScheduledAction' {} Text
a -> ModifyScheduledAction
s {$sel:scheduledActionName:ModifyScheduledAction' :: Text
scheduledActionName = Text
a} :: ModifyScheduledAction)

instance Core.AWSRequest ModifyScheduledAction where
  type
    AWSResponse ModifyScheduledAction =
      ScheduledAction
  request :: (Service -> Service)
-> ModifyScheduledAction -> Request ModifyScheduledAction
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 ModifyScheduledAction
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ModifyScheduledAction)))
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
"ModifyScheduledActionResult"
      (\Int
s ResponseHeaders
h [Node]
x -> forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)

instance Prelude.Hashable ModifyScheduledAction where
  hashWithSalt :: Int -> ModifyScheduledAction -> Int
hashWithSalt Int
_salt ModifyScheduledAction' {Maybe Bool
Maybe Text
Maybe ISO8601
Maybe ScheduledActionType
Text
scheduledActionName :: Text
targetAction :: Maybe ScheduledActionType
startTime :: Maybe ISO8601
scheduledActionDescription :: Maybe Text
schedule :: Maybe Text
iamRole :: Maybe Text
endTime :: Maybe ISO8601
enable :: Maybe Bool
$sel:scheduledActionName:ModifyScheduledAction' :: ModifyScheduledAction -> Text
$sel:targetAction:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ScheduledActionType
$sel:startTime:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ISO8601
$sel:scheduledActionDescription:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
$sel:schedule:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
$sel:iamRole:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
$sel:endTime:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ISO8601
$sel:enable:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enable
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
iamRole
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
schedule
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
scheduledActionDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ScheduledActionType
targetAction
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
scheduledActionName

instance Prelude.NFData ModifyScheduledAction where
  rnf :: ModifyScheduledAction -> ()
rnf ModifyScheduledAction' {Maybe Bool
Maybe Text
Maybe ISO8601
Maybe ScheduledActionType
Text
scheduledActionName :: Text
targetAction :: Maybe ScheduledActionType
startTime :: Maybe ISO8601
scheduledActionDescription :: Maybe Text
schedule :: Maybe Text
iamRole :: Maybe Text
endTime :: Maybe ISO8601
enable :: Maybe Bool
$sel:scheduledActionName:ModifyScheduledAction' :: ModifyScheduledAction -> Text
$sel:targetAction:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ScheduledActionType
$sel:startTime:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ISO8601
$sel:scheduledActionDescription:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
$sel:schedule:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
$sel:iamRole:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
$sel:endTime:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ISO8601
$sel:enable:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enable
      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 Text
iamRole
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
schedule
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
scheduledActionDescription
      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 ScheduledActionType
targetAction
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
scheduledActionName

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

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

instance Data.ToQuery ModifyScheduledAction where
  toQuery :: ModifyScheduledAction -> QueryString
toQuery ModifyScheduledAction' {Maybe Bool
Maybe Text
Maybe ISO8601
Maybe ScheduledActionType
Text
scheduledActionName :: Text
targetAction :: Maybe ScheduledActionType
startTime :: Maybe ISO8601
scheduledActionDescription :: Maybe Text
schedule :: Maybe Text
iamRole :: Maybe Text
endTime :: Maybe ISO8601
enable :: Maybe Bool
$sel:scheduledActionName:ModifyScheduledAction' :: ModifyScheduledAction -> Text
$sel:targetAction:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ScheduledActionType
$sel:startTime:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ISO8601
$sel:scheduledActionDescription:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
$sel:schedule:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
$sel:iamRole:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Text
$sel:endTime:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe ISO8601
$sel:enable:ModifyScheduledAction' :: ModifyScheduledAction -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ModifyScheduledAction" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: Prelude.ByteString),
        ByteString
"Enable" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
enable,
        ByteString
"EndTime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
endTime,
        ByteString
"IamRole" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
iamRole,
        ByteString
"Schedule" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
schedule,
        ByteString
"ScheduledActionDescription"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
scheduledActionDescription,
        ByteString
"StartTime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
startTime,
        ByteString
"TargetAction" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ScheduledActionType
targetAction,
        ByteString
"ScheduledActionName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
scheduledActionName
      ]