{-# 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.Redshift.Types.ScheduledAction
-- 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.Redshift.Types.ScheduledAction 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.Internal
import Amazonka.Redshift.Types.ScheduledActionState
import Amazonka.Redshift.Types.ScheduledActionType

-- | Describes a scheduled action. You can use a scheduled action to trigger
-- some Amazon Redshift API operations on a schedule. For information about
-- which API operations can be scheduled, see ScheduledActionType.
--
-- /See:/ 'newScheduledAction' smart constructor.
data ScheduledAction = ScheduledAction'
  { -- | The end time in UTC when the schedule is no longer active. After this
    -- time, the scheduled action does not trigger.
    ScheduledAction -> Maybe ISO8601
endTime :: Prelude.Maybe Data.ISO8601,
    -- | The IAM role to assume to run the scheduled action. This IAM role must
    -- have permission to run the Amazon Redshift API operation in the
    -- scheduled action. This IAM role must allow the Amazon Redshift scheduler
    -- (Principal scheduler.redshift.amazonaws.com) to assume permissions on
    -- your behalf. For more information about the IAM role to use with the
    -- Amazon Redshift scheduler, see
    -- <https://docs.aws.amazon.com/redshift/latest/mgmt/redshift-iam-access-control-identity-based.html Using Identity-Based Policies for Amazon Redshift>
    -- in the /Amazon Redshift Cluster Management Guide/.
    ScheduledAction -> Maybe Text
iamRole :: Prelude.Maybe Prelude.Text,
    -- | List of times when the scheduled action will run.
    ScheduledAction -> Maybe [ISO8601]
nextInvocations :: Prelude.Maybe [Data.ISO8601],
    -- | The schedule for a one-time (at format) or recurring (cron format)
    -- scheduled action. Schedule invocations must be separated by at least one
    -- hour.
    --
    -- Format of at expressions is \"@at(yyyy-mm-ddThh:mm:ss)@\". For example,
    -- \"@at(2016-03-04T17:27:00)@\".
    --
    -- Format of cron expressions is
    -- \"@cron(Minutes Hours Day-of-month Month Day-of-week Year)@\". For
    -- example, \"@cron(0 10 ? * MON *)@\". For more information, see
    -- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/events/ScheduledEvents.html#CronExpressions Cron Expressions>
    -- in the /Amazon CloudWatch Events User Guide/.
    ScheduledAction -> Maybe Text
schedule :: Prelude.Maybe Prelude.Text,
    -- | The description of the scheduled action.
    ScheduledAction -> Maybe Text
scheduledActionDescription :: Prelude.Maybe Prelude.Text,
    -- | The name of the scheduled action.
    ScheduledAction -> Maybe Text
scheduledActionName :: Prelude.Maybe Prelude.Text,
    -- | The start time in UTC when the schedule is active. Before this time, the
    -- scheduled action does not trigger.
    ScheduledAction -> Maybe ISO8601
startTime :: Prelude.Maybe Data.ISO8601,
    -- | The state of the scheduled action. For example, @DISABLED@.
    ScheduledAction -> Maybe ScheduledActionState
state :: Prelude.Maybe ScheduledActionState,
    -- | A JSON format string of the Amazon Redshift API operation with input
    -- parameters.
    --
    -- \"@{\\\"ResizeCluster\\\":{\\\"NodeType\\\":\\\"ds2.8xlarge\\\",\\\"ClusterIdentifier\\\":\\\"my-test-cluster\\\",\\\"NumberOfNodes\\\":3}}@\".
    ScheduledAction -> Maybe ScheduledActionType
targetAction :: Prelude.Maybe ScheduledActionType
  }
  deriving (ScheduledAction -> ScheduledAction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScheduledAction -> ScheduledAction -> Bool
$c/= :: ScheduledAction -> ScheduledAction -> Bool
== :: ScheduledAction -> ScheduledAction -> Bool
$c== :: ScheduledAction -> ScheduledAction -> Bool
Prelude.Eq, ReadPrec [ScheduledAction]
ReadPrec ScheduledAction
Int -> ReadS ScheduledAction
ReadS [ScheduledAction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ScheduledAction]
$creadListPrec :: ReadPrec [ScheduledAction]
readPrec :: ReadPrec ScheduledAction
$creadPrec :: ReadPrec ScheduledAction
readList :: ReadS [ScheduledAction]
$creadList :: ReadS [ScheduledAction]
readsPrec :: Int -> ReadS ScheduledAction
$creadsPrec :: Int -> ReadS ScheduledAction
Prelude.Read, Int -> ScheduledAction -> ShowS
[ScheduledAction] -> ShowS
ScheduledAction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScheduledAction] -> ShowS
$cshowList :: [ScheduledAction] -> ShowS
show :: ScheduledAction -> String
$cshow :: ScheduledAction -> String
showsPrec :: Int -> ScheduledAction -> ShowS
$cshowsPrec :: Int -> ScheduledAction -> ShowS
Prelude.Show, forall x. Rep ScheduledAction x -> ScheduledAction
forall x. ScheduledAction -> Rep ScheduledAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScheduledAction x -> ScheduledAction
$cfrom :: forall x. ScheduledAction -> Rep ScheduledAction x
Prelude.Generic)

-- |
-- Create a value of 'ScheduledAction' 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:
--
-- 'endTime', 'scheduledAction_endTime' - The end time in UTC when the schedule is no longer active. After this
-- time, the scheduled action does not trigger.
--
-- 'iamRole', 'scheduledAction_iamRole' - The IAM role to assume to run the scheduled action. This IAM role must
-- have permission to run the Amazon Redshift API operation in the
-- scheduled action. This IAM role must allow the Amazon Redshift scheduler
-- (Principal scheduler.redshift.amazonaws.com) to assume permissions on
-- your behalf. For more information about the IAM role to use with the
-- Amazon Redshift scheduler, see
-- <https://docs.aws.amazon.com/redshift/latest/mgmt/redshift-iam-access-control-identity-based.html Using Identity-Based Policies for Amazon Redshift>
-- in the /Amazon Redshift Cluster Management Guide/.
--
-- 'nextInvocations', 'scheduledAction_nextInvocations' - List of times when the scheduled action will run.
--
-- 'schedule', 'scheduledAction_schedule' - The schedule for a one-time (at format) or recurring (cron format)
-- scheduled action. Schedule invocations must be separated by at least one
-- hour.
--
-- Format of at expressions is \"@at(yyyy-mm-ddThh:mm:ss)@\". For example,
-- \"@at(2016-03-04T17:27:00)@\".
--
-- Format of cron expressions is
-- \"@cron(Minutes Hours Day-of-month Month Day-of-week Year)@\". For
-- example, \"@cron(0 10 ? * MON *)@\". For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/events/ScheduledEvents.html#CronExpressions Cron Expressions>
-- in the /Amazon CloudWatch Events User Guide/.
--
-- 'scheduledActionDescription', 'scheduledAction_scheduledActionDescription' - The description of the scheduled action.
--
-- 'scheduledActionName', 'scheduledAction_scheduledActionName' - The name of the scheduled action.
--
-- 'startTime', 'scheduledAction_startTime' - The start time in UTC when the schedule is active. Before this time, the
-- scheduled action does not trigger.
--
-- 'state', 'scheduledAction_state' - The state of the scheduled action. For example, @DISABLED@.
--
-- 'targetAction', 'scheduledAction_targetAction' - A JSON format string of the Amazon Redshift API operation with input
-- parameters.
--
-- \"@{\\\"ResizeCluster\\\":{\\\"NodeType\\\":\\\"ds2.8xlarge\\\",\\\"ClusterIdentifier\\\":\\\"my-test-cluster\\\",\\\"NumberOfNodes\\\":3}}@\".
newScheduledAction ::
  ScheduledAction
newScheduledAction :: ScheduledAction
newScheduledAction =
  ScheduledAction'
    { $sel:endTime:ScheduledAction' :: Maybe ISO8601
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:iamRole:ScheduledAction' :: Maybe Text
iamRole = forall a. Maybe a
Prelude.Nothing,
      $sel:nextInvocations:ScheduledAction' :: Maybe [ISO8601]
nextInvocations = forall a. Maybe a
Prelude.Nothing,
      $sel:schedule:ScheduledAction' :: Maybe Text
schedule = forall a. Maybe a
Prelude.Nothing,
      $sel:scheduledActionDescription:ScheduledAction' :: Maybe Text
scheduledActionDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:scheduledActionName:ScheduledAction' :: Maybe Text
scheduledActionName = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:ScheduledAction' :: Maybe ISO8601
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:state:ScheduledAction' :: Maybe ScheduledActionState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:targetAction:ScheduledAction' :: Maybe ScheduledActionType
targetAction = forall a. Maybe a
Prelude.Nothing
    }

-- | The end time in UTC when the schedule is no longer active. After this
-- time, the scheduled action does not trigger.
scheduledAction_endTime :: Lens.Lens' ScheduledAction (Prelude.Maybe Prelude.UTCTime)
scheduledAction_endTime :: Lens' ScheduledAction (Maybe UTCTime)
scheduledAction_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledAction' {Maybe ISO8601
endTime :: Maybe ISO8601
$sel:endTime:ScheduledAction' :: ScheduledAction -> Maybe ISO8601
endTime} -> Maybe ISO8601
endTime) (\s :: ScheduledAction
s@ScheduledAction' {} Maybe ISO8601
a -> ScheduledAction
s {$sel:endTime:ScheduledAction' :: Maybe ISO8601
endTime = Maybe ISO8601
a} :: ScheduledAction) 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 IAM role to assume to run the scheduled action. This IAM role must
-- have permission to run the Amazon Redshift API operation in the
-- scheduled action. This IAM role must allow the Amazon Redshift scheduler
-- (Principal scheduler.redshift.amazonaws.com) to assume permissions on
-- your behalf. For more information about the IAM role to use with the
-- Amazon Redshift scheduler, see
-- <https://docs.aws.amazon.com/redshift/latest/mgmt/redshift-iam-access-control-identity-based.html Using Identity-Based Policies for Amazon Redshift>
-- in the /Amazon Redshift Cluster Management Guide/.
scheduledAction_iamRole :: Lens.Lens' ScheduledAction (Prelude.Maybe Prelude.Text)
scheduledAction_iamRole :: Lens' ScheduledAction (Maybe Text)
scheduledAction_iamRole = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledAction' {Maybe Text
iamRole :: Maybe Text
$sel:iamRole:ScheduledAction' :: ScheduledAction -> Maybe Text
iamRole} -> Maybe Text
iamRole) (\s :: ScheduledAction
s@ScheduledAction' {} Maybe Text
a -> ScheduledAction
s {$sel:iamRole:ScheduledAction' :: Maybe Text
iamRole = Maybe Text
a} :: ScheduledAction)

-- | List of times when the scheduled action will run.
scheduledAction_nextInvocations :: Lens.Lens' ScheduledAction (Prelude.Maybe [Prelude.UTCTime])
scheduledAction_nextInvocations :: Lens' ScheduledAction (Maybe [UTCTime])
scheduledAction_nextInvocations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledAction' {Maybe [ISO8601]
nextInvocations :: Maybe [ISO8601]
$sel:nextInvocations:ScheduledAction' :: ScheduledAction -> Maybe [ISO8601]
nextInvocations} -> Maybe [ISO8601]
nextInvocations) (\s :: ScheduledAction
s@ScheduledAction' {} Maybe [ISO8601]
a -> ScheduledAction
s {$sel:nextInvocations:ScheduledAction' :: Maybe [ISO8601]
nextInvocations = Maybe [ISO8601]
a} :: ScheduledAction) 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 schedule for a one-time (at format) or recurring (cron format)
-- scheduled action. Schedule invocations must be separated by at least one
-- hour.
--
-- Format of at expressions is \"@at(yyyy-mm-ddThh:mm:ss)@\". For example,
-- \"@at(2016-03-04T17:27:00)@\".
--
-- Format of cron expressions is
-- \"@cron(Minutes Hours Day-of-month Month Day-of-week Year)@\". For
-- example, \"@cron(0 10 ? * MON *)@\". For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/events/ScheduledEvents.html#CronExpressions Cron Expressions>
-- in the /Amazon CloudWatch Events User Guide/.
scheduledAction_schedule :: Lens.Lens' ScheduledAction (Prelude.Maybe Prelude.Text)
scheduledAction_schedule :: Lens' ScheduledAction (Maybe Text)
scheduledAction_schedule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledAction' {Maybe Text
schedule :: Maybe Text
$sel:schedule:ScheduledAction' :: ScheduledAction -> Maybe Text
schedule} -> Maybe Text
schedule) (\s :: ScheduledAction
s@ScheduledAction' {} Maybe Text
a -> ScheduledAction
s {$sel:schedule:ScheduledAction' :: Maybe Text
schedule = Maybe Text
a} :: ScheduledAction)

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

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

-- | The start time in UTC when the schedule is active. Before this time, the
-- scheduled action does not trigger.
scheduledAction_startTime :: Lens.Lens' ScheduledAction (Prelude.Maybe Prelude.UTCTime)
scheduledAction_startTime :: Lens' ScheduledAction (Maybe UTCTime)
scheduledAction_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledAction' {Maybe ISO8601
startTime :: Maybe ISO8601
$sel:startTime:ScheduledAction' :: ScheduledAction -> Maybe ISO8601
startTime} -> Maybe ISO8601
startTime) (\s :: ScheduledAction
s@ScheduledAction' {} Maybe ISO8601
a -> ScheduledAction
s {$sel:startTime:ScheduledAction' :: Maybe ISO8601
startTime = Maybe ISO8601
a} :: ScheduledAction) 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 state of the scheduled action. For example, @DISABLED@.
scheduledAction_state :: Lens.Lens' ScheduledAction (Prelude.Maybe ScheduledActionState)
scheduledAction_state :: Lens' ScheduledAction (Maybe ScheduledActionState)
scheduledAction_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledAction' {Maybe ScheduledActionState
state :: Maybe ScheduledActionState
$sel:state:ScheduledAction' :: ScheduledAction -> Maybe ScheduledActionState
state} -> Maybe ScheduledActionState
state) (\s :: ScheduledAction
s@ScheduledAction' {} Maybe ScheduledActionState
a -> ScheduledAction
s {$sel:state:ScheduledAction' :: Maybe ScheduledActionState
state = Maybe ScheduledActionState
a} :: ScheduledAction)

-- | A JSON format string of the Amazon Redshift API operation with input
-- parameters.
--
-- \"@{\\\"ResizeCluster\\\":{\\\"NodeType\\\":\\\"ds2.8xlarge\\\",\\\"ClusterIdentifier\\\":\\\"my-test-cluster\\\",\\\"NumberOfNodes\\\":3}}@\".
scheduledAction_targetAction :: Lens.Lens' ScheduledAction (Prelude.Maybe ScheduledActionType)
scheduledAction_targetAction :: Lens' ScheduledAction (Maybe ScheduledActionType)
scheduledAction_targetAction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ScheduledAction' {Maybe ScheduledActionType
targetAction :: Maybe ScheduledActionType
$sel:targetAction:ScheduledAction' :: ScheduledAction -> Maybe ScheduledActionType
targetAction} -> Maybe ScheduledActionType
targetAction) (\s :: ScheduledAction
s@ScheduledAction' {} Maybe ScheduledActionType
a -> ScheduledAction
s {$sel:targetAction:ScheduledAction' :: Maybe ScheduledActionType
targetAction = Maybe ScheduledActionType
a} :: ScheduledAction)

instance Data.FromXML ScheduledAction where
  parseXML :: [Node] -> Either String ScheduledAction
parseXML [Node]
x =
    Maybe ISO8601
-> Maybe Text
-> Maybe [ISO8601]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ISO8601
-> Maybe ScheduledActionState
-> Maybe ScheduledActionType
-> ScheduledAction
ScheduledAction'
      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
"EndTime")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"IamRole")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"NextInvocations"
                      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
"ScheduledActionTime")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Schedule")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ScheduledActionDescription")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ScheduledActionName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StartTime")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"State")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TargetAction")

instance Prelude.Hashable ScheduledAction where
  hashWithSalt :: Int -> ScheduledAction -> Int
hashWithSalt Int
_salt ScheduledAction' {Maybe [ISO8601]
Maybe Text
Maybe ISO8601
Maybe ScheduledActionState
Maybe ScheduledActionType
targetAction :: Maybe ScheduledActionType
state :: Maybe ScheduledActionState
startTime :: Maybe ISO8601
scheduledActionName :: Maybe Text
scheduledActionDescription :: Maybe Text
schedule :: Maybe Text
nextInvocations :: Maybe [ISO8601]
iamRole :: Maybe Text
endTime :: Maybe ISO8601
$sel:targetAction:ScheduledAction' :: ScheduledAction -> Maybe ScheduledActionType
$sel:state:ScheduledAction' :: ScheduledAction -> Maybe ScheduledActionState
$sel:startTime:ScheduledAction' :: ScheduledAction -> Maybe ISO8601
$sel:scheduledActionName:ScheduledAction' :: ScheduledAction -> Maybe Text
$sel:scheduledActionDescription:ScheduledAction' :: ScheduledAction -> Maybe Text
$sel:schedule:ScheduledAction' :: ScheduledAction -> Maybe Text
$sel:nextInvocations:ScheduledAction' :: ScheduledAction -> Maybe [ISO8601]
$sel:iamRole:ScheduledAction' :: ScheduledAction -> Maybe Text
$sel:endTime:ScheduledAction' :: ScheduledAction -> Maybe ISO8601
..} =
    Int
_salt
      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 [ISO8601]
nextInvocations
      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 Text
scheduledActionName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ScheduledActionState
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ScheduledActionType
targetAction

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