{-# 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.SSM.UpdateMaintenanceWindow
-- 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 an existing maintenance window. Only specified parameters are
-- modified.
--
-- The value you specify for @Duration@ determines the specific end time
-- for the maintenance window based on the time it begins. No maintenance
-- window tasks are permitted to start after the resulting endtime minus
-- the number of hours you specify for @Cutoff@. For example, if the
-- maintenance window starts at 3 PM, the duration is three hours, and the
-- value you specify for @Cutoff@ is one hour, no maintenance window tasks
-- can start after 5 PM.
module Amazonka.SSM.UpdateMaintenanceWindow
  ( -- * Creating a Request
    UpdateMaintenanceWindow (..),
    newUpdateMaintenanceWindow,

    -- * Request Lenses
    updateMaintenanceWindow_allowUnassociatedTargets,
    updateMaintenanceWindow_cutoff,
    updateMaintenanceWindow_description,
    updateMaintenanceWindow_duration,
    updateMaintenanceWindow_enabled,
    updateMaintenanceWindow_endDate,
    updateMaintenanceWindow_name,
    updateMaintenanceWindow_replace,
    updateMaintenanceWindow_schedule,
    updateMaintenanceWindow_scheduleOffset,
    updateMaintenanceWindow_scheduleTimezone,
    updateMaintenanceWindow_startDate,
    updateMaintenanceWindow_windowId,

    -- * Destructuring the Response
    UpdateMaintenanceWindowResponse (..),
    newUpdateMaintenanceWindowResponse,

    -- * Response Lenses
    updateMaintenanceWindowResponse_allowUnassociatedTargets,
    updateMaintenanceWindowResponse_cutoff,
    updateMaintenanceWindowResponse_description,
    updateMaintenanceWindowResponse_duration,
    updateMaintenanceWindowResponse_enabled,
    updateMaintenanceWindowResponse_endDate,
    updateMaintenanceWindowResponse_name,
    updateMaintenanceWindowResponse_schedule,
    updateMaintenanceWindowResponse_scheduleOffset,
    updateMaintenanceWindowResponse_scheduleTimezone,
    updateMaintenanceWindowResponse_startDate,
    updateMaintenanceWindowResponse_windowId,
    updateMaintenanceWindowResponse_httpStatus,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SSM.Types

-- | /See:/ 'newUpdateMaintenanceWindow' smart constructor.
data UpdateMaintenanceWindow = UpdateMaintenanceWindow'
  { -- | Whether targets must be registered with the maintenance window before
    -- tasks can be defined for those targets.
    UpdateMaintenanceWindow -> Maybe Bool
allowUnassociatedTargets :: Prelude.Maybe Prelude.Bool,
    -- | The number of hours before the end of the maintenance window that Amazon
    -- Web Services Systems Manager stops scheduling new tasks for execution.
    UpdateMaintenanceWindow -> Maybe Natural
cutoff :: Prelude.Maybe Prelude.Natural,
    -- | An optional description for the update request.
    UpdateMaintenanceWindow -> Maybe (Sensitive Text)
description :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The duration of the maintenance window in hours.
    UpdateMaintenanceWindow -> Maybe Natural
duration :: Prelude.Maybe Prelude.Natural,
    -- | Whether the maintenance window is enabled.
    UpdateMaintenanceWindow -> Maybe Bool
enabled :: Prelude.Maybe Prelude.Bool,
    -- | The date and time, in ISO-8601 Extended format, for when you want the
    -- maintenance window to become inactive. @EndDate@ allows you to set a
    -- date and time in the future when the maintenance window will no longer
    -- run.
    UpdateMaintenanceWindow -> Maybe Text
endDate :: Prelude.Maybe Prelude.Text,
    -- | The name of the maintenance window.
    UpdateMaintenanceWindow -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | If @True@, then all fields that are required by the
    -- CreateMaintenanceWindow operation are also required for this API
    -- request. Optional fields that aren\'t specified are set to null.
    UpdateMaintenanceWindow -> Maybe Bool
replace :: Prelude.Maybe Prelude.Bool,
    -- | The schedule of the maintenance window in the form of a cron or rate
    -- expression.
    UpdateMaintenanceWindow -> Maybe Text
schedule :: Prelude.Maybe Prelude.Text,
    -- | The number of days to wait after the date and time specified by a cron
    -- expression before running the maintenance window.
    --
    -- For example, the following cron expression schedules a maintenance
    -- window to run the third Tuesday of every month at 11:30 PM.
    --
    -- @cron(30 23 ? * TUE#3 *)@
    --
    -- If the schedule offset is @2@, the maintenance window won\'t run until
    -- two days later.
    UpdateMaintenanceWindow -> Maybe Natural
scheduleOffset :: Prelude.Maybe Prelude.Natural,
    -- | The time zone that the scheduled maintenance window executions are based
    -- on, in Internet Assigned Numbers Authority (IANA) format. For example:
    -- \"America\/Los_Angeles\", \"UTC\", or \"Asia\/Seoul\". For more
    -- information, see the
    -- <https://www.iana.org/time-zones Time Zone Database> on the IANA
    -- website.
    UpdateMaintenanceWindow -> Maybe Text
scheduleTimezone :: Prelude.Maybe Prelude.Text,
    -- | The date and time, in ISO-8601 Extended format, for when you want the
    -- maintenance window to become active. @StartDate@ allows you to delay
    -- activation of the maintenance window until the specified future date.
    UpdateMaintenanceWindow -> Maybe Text
startDate :: Prelude.Maybe Prelude.Text,
    -- | The ID of the maintenance window to update.
    UpdateMaintenanceWindow -> Text
windowId :: Prelude.Text
  }
  deriving (UpdateMaintenanceWindow -> UpdateMaintenanceWindow -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateMaintenanceWindow -> UpdateMaintenanceWindow -> Bool
$c/= :: UpdateMaintenanceWindow -> UpdateMaintenanceWindow -> Bool
== :: UpdateMaintenanceWindow -> UpdateMaintenanceWindow -> Bool
$c== :: UpdateMaintenanceWindow -> UpdateMaintenanceWindow -> Bool
Prelude.Eq, Int -> UpdateMaintenanceWindow -> ShowS
[UpdateMaintenanceWindow] -> ShowS
UpdateMaintenanceWindow -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateMaintenanceWindow] -> ShowS
$cshowList :: [UpdateMaintenanceWindow] -> ShowS
show :: UpdateMaintenanceWindow -> String
$cshow :: UpdateMaintenanceWindow -> String
showsPrec :: Int -> UpdateMaintenanceWindow -> ShowS
$cshowsPrec :: Int -> UpdateMaintenanceWindow -> ShowS
Prelude.Show, forall x. Rep UpdateMaintenanceWindow x -> UpdateMaintenanceWindow
forall x. UpdateMaintenanceWindow -> Rep UpdateMaintenanceWindow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateMaintenanceWindow x -> UpdateMaintenanceWindow
$cfrom :: forall x. UpdateMaintenanceWindow -> Rep UpdateMaintenanceWindow x
Prelude.Generic)

-- |
-- Create a value of 'UpdateMaintenanceWindow' 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:
--
-- 'allowUnassociatedTargets', 'updateMaintenanceWindow_allowUnassociatedTargets' - Whether targets must be registered with the maintenance window before
-- tasks can be defined for those targets.
--
-- 'cutoff', 'updateMaintenanceWindow_cutoff' - The number of hours before the end of the maintenance window that Amazon
-- Web Services Systems Manager stops scheduling new tasks for execution.
--
-- 'description', 'updateMaintenanceWindow_description' - An optional description for the update request.
--
-- 'duration', 'updateMaintenanceWindow_duration' - The duration of the maintenance window in hours.
--
-- 'enabled', 'updateMaintenanceWindow_enabled' - Whether the maintenance window is enabled.
--
-- 'endDate', 'updateMaintenanceWindow_endDate' - The date and time, in ISO-8601 Extended format, for when you want the
-- maintenance window to become inactive. @EndDate@ allows you to set a
-- date and time in the future when the maintenance window will no longer
-- run.
--
-- 'name', 'updateMaintenanceWindow_name' - The name of the maintenance window.
--
-- 'replace', 'updateMaintenanceWindow_replace' - If @True@, then all fields that are required by the
-- CreateMaintenanceWindow operation are also required for this API
-- request. Optional fields that aren\'t specified are set to null.
--
-- 'schedule', 'updateMaintenanceWindow_schedule' - The schedule of the maintenance window in the form of a cron or rate
-- expression.
--
-- 'scheduleOffset', 'updateMaintenanceWindow_scheduleOffset' - The number of days to wait after the date and time specified by a cron
-- expression before running the maintenance window.
--
-- For example, the following cron expression schedules a maintenance
-- window to run the third Tuesday of every month at 11:30 PM.
--
-- @cron(30 23 ? * TUE#3 *)@
--
-- If the schedule offset is @2@, the maintenance window won\'t run until
-- two days later.
--
-- 'scheduleTimezone', 'updateMaintenanceWindow_scheduleTimezone' - The time zone that the scheduled maintenance window executions are based
-- on, in Internet Assigned Numbers Authority (IANA) format. For example:
-- \"America\/Los_Angeles\", \"UTC\", or \"Asia\/Seoul\". For more
-- information, see the
-- <https://www.iana.org/time-zones Time Zone Database> on the IANA
-- website.
--
-- 'startDate', 'updateMaintenanceWindow_startDate' - The date and time, in ISO-8601 Extended format, for when you want the
-- maintenance window to become active. @StartDate@ allows you to delay
-- activation of the maintenance window until the specified future date.
--
-- 'windowId', 'updateMaintenanceWindow_windowId' - The ID of the maintenance window to update.
newUpdateMaintenanceWindow ::
  -- | 'windowId'
  Prelude.Text ->
  UpdateMaintenanceWindow
newUpdateMaintenanceWindow :: Text -> UpdateMaintenanceWindow
newUpdateMaintenanceWindow Text
pWindowId_ =
  UpdateMaintenanceWindow'
    { $sel:allowUnassociatedTargets:UpdateMaintenanceWindow' :: Maybe Bool
allowUnassociatedTargets =
        forall a. Maybe a
Prelude.Nothing,
      $sel:cutoff:UpdateMaintenanceWindow' :: Maybe Natural
cutoff = forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateMaintenanceWindow' :: Maybe (Sensitive Text)
description = forall a. Maybe a
Prelude.Nothing,
      $sel:duration:UpdateMaintenanceWindow' :: Maybe Natural
duration = forall a. Maybe a
Prelude.Nothing,
      $sel:enabled:UpdateMaintenanceWindow' :: Maybe Bool
enabled = forall a. Maybe a
Prelude.Nothing,
      $sel:endDate:UpdateMaintenanceWindow' :: Maybe Text
endDate = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateMaintenanceWindow' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:replace:UpdateMaintenanceWindow' :: Maybe Bool
replace = forall a. Maybe a
Prelude.Nothing,
      $sel:schedule:UpdateMaintenanceWindow' :: Maybe Text
schedule = forall a. Maybe a
Prelude.Nothing,
      $sel:scheduleOffset:UpdateMaintenanceWindow' :: Maybe Natural
scheduleOffset = forall a. Maybe a
Prelude.Nothing,
      $sel:scheduleTimezone:UpdateMaintenanceWindow' :: Maybe Text
scheduleTimezone = forall a. Maybe a
Prelude.Nothing,
      $sel:startDate:UpdateMaintenanceWindow' :: Maybe Text
startDate = forall a. Maybe a
Prelude.Nothing,
      $sel:windowId:UpdateMaintenanceWindow' :: Text
windowId = Text
pWindowId_
    }

-- | Whether targets must be registered with the maintenance window before
-- tasks can be defined for those targets.
updateMaintenanceWindow_allowUnassociatedTargets :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Bool)
updateMaintenanceWindow_allowUnassociatedTargets :: Lens' UpdateMaintenanceWindow (Maybe Bool)
updateMaintenanceWindow_allowUnassociatedTargets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe Bool
allowUnassociatedTargets :: Maybe Bool
$sel:allowUnassociatedTargets:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
allowUnassociatedTargets} -> Maybe Bool
allowUnassociatedTargets) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe Bool
a -> UpdateMaintenanceWindow
s {$sel:allowUnassociatedTargets:UpdateMaintenanceWindow' :: Maybe Bool
allowUnassociatedTargets = Maybe Bool
a} :: UpdateMaintenanceWindow)

-- | The number of hours before the end of the maintenance window that Amazon
-- Web Services Systems Manager stops scheduling new tasks for execution.
updateMaintenanceWindow_cutoff :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Natural)
updateMaintenanceWindow_cutoff :: Lens' UpdateMaintenanceWindow (Maybe Natural)
updateMaintenanceWindow_cutoff = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe Natural
cutoff :: Maybe Natural
$sel:cutoff:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
cutoff} -> Maybe Natural
cutoff) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe Natural
a -> UpdateMaintenanceWindow
s {$sel:cutoff:UpdateMaintenanceWindow' :: Maybe Natural
cutoff = Maybe Natural
a} :: UpdateMaintenanceWindow)

-- | An optional description for the update request.
updateMaintenanceWindow_description :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Text)
updateMaintenanceWindow_description :: Lens' UpdateMaintenanceWindow (Maybe Text)
updateMaintenanceWindow_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:description:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe (Sensitive Text)
description} -> Maybe (Sensitive Text)
description) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe (Sensitive Text)
a -> UpdateMaintenanceWindow
s {$sel:description:UpdateMaintenanceWindow' :: Maybe (Sensitive Text)
description = Maybe (Sensitive Text)
a} :: UpdateMaintenanceWindow) 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. Iso' (Sensitive a) a
Data._Sensitive

-- | The duration of the maintenance window in hours.
updateMaintenanceWindow_duration :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Natural)
updateMaintenanceWindow_duration :: Lens' UpdateMaintenanceWindow (Maybe Natural)
updateMaintenanceWindow_duration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe Natural
duration :: Maybe Natural
$sel:duration:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
duration} -> Maybe Natural
duration) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe Natural
a -> UpdateMaintenanceWindow
s {$sel:duration:UpdateMaintenanceWindow' :: Maybe Natural
duration = Maybe Natural
a} :: UpdateMaintenanceWindow)

-- | Whether the maintenance window is enabled.
updateMaintenanceWindow_enabled :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Bool)
updateMaintenanceWindow_enabled :: Lens' UpdateMaintenanceWindow (Maybe Bool)
updateMaintenanceWindow_enabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe Bool
enabled :: Maybe Bool
$sel:enabled:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
enabled} -> Maybe Bool
enabled) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe Bool
a -> UpdateMaintenanceWindow
s {$sel:enabled:UpdateMaintenanceWindow' :: Maybe Bool
enabled = Maybe Bool
a} :: UpdateMaintenanceWindow)

-- | The date and time, in ISO-8601 Extended format, for when you want the
-- maintenance window to become inactive. @EndDate@ allows you to set a
-- date and time in the future when the maintenance window will no longer
-- run.
updateMaintenanceWindow_endDate :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Text)
updateMaintenanceWindow_endDate :: Lens' UpdateMaintenanceWindow (Maybe Text)
updateMaintenanceWindow_endDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe Text
endDate :: Maybe Text
$sel:endDate:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
endDate} -> Maybe Text
endDate) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe Text
a -> UpdateMaintenanceWindow
s {$sel:endDate:UpdateMaintenanceWindow' :: Maybe Text
endDate = Maybe Text
a} :: UpdateMaintenanceWindow)

-- | The name of the maintenance window.
updateMaintenanceWindow_name :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Text)
updateMaintenanceWindow_name :: Lens' UpdateMaintenanceWindow (Maybe Text)
updateMaintenanceWindow_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe Text
name :: Maybe Text
$sel:name:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe Text
a -> UpdateMaintenanceWindow
s {$sel:name:UpdateMaintenanceWindow' :: Maybe Text
name = Maybe Text
a} :: UpdateMaintenanceWindow)

-- | If @True@, then all fields that are required by the
-- CreateMaintenanceWindow operation are also required for this API
-- request. Optional fields that aren\'t specified are set to null.
updateMaintenanceWindow_replace :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Bool)
updateMaintenanceWindow_replace :: Lens' UpdateMaintenanceWindow (Maybe Bool)
updateMaintenanceWindow_replace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe Bool
replace :: Maybe Bool
$sel:replace:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
replace} -> Maybe Bool
replace) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe Bool
a -> UpdateMaintenanceWindow
s {$sel:replace:UpdateMaintenanceWindow' :: Maybe Bool
replace = Maybe Bool
a} :: UpdateMaintenanceWindow)

-- | The schedule of the maintenance window in the form of a cron or rate
-- expression.
updateMaintenanceWindow_schedule :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Text)
updateMaintenanceWindow_schedule :: Lens' UpdateMaintenanceWindow (Maybe Text)
updateMaintenanceWindow_schedule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe Text
schedule :: Maybe Text
$sel:schedule:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
schedule} -> Maybe Text
schedule) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe Text
a -> UpdateMaintenanceWindow
s {$sel:schedule:UpdateMaintenanceWindow' :: Maybe Text
schedule = Maybe Text
a} :: UpdateMaintenanceWindow)

-- | The number of days to wait after the date and time specified by a cron
-- expression before running the maintenance window.
--
-- For example, the following cron expression schedules a maintenance
-- window to run the third Tuesday of every month at 11:30 PM.
--
-- @cron(30 23 ? * TUE#3 *)@
--
-- If the schedule offset is @2@, the maintenance window won\'t run until
-- two days later.
updateMaintenanceWindow_scheduleOffset :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Natural)
updateMaintenanceWindow_scheduleOffset :: Lens' UpdateMaintenanceWindow (Maybe Natural)
updateMaintenanceWindow_scheduleOffset = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe Natural
scheduleOffset :: Maybe Natural
$sel:scheduleOffset:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
scheduleOffset} -> Maybe Natural
scheduleOffset) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe Natural
a -> UpdateMaintenanceWindow
s {$sel:scheduleOffset:UpdateMaintenanceWindow' :: Maybe Natural
scheduleOffset = Maybe Natural
a} :: UpdateMaintenanceWindow)

-- | The time zone that the scheduled maintenance window executions are based
-- on, in Internet Assigned Numbers Authority (IANA) format. For example:
-- \"America\/Los_Angeles\", \"UTC\", or \"Asia\/Seoul\". For more
-- information, see the
-- <https://www.iana.org/time-zones Time Zone Database> on the IANA
-- website.
updateMaintenanceWindow_scheduleTimezone :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Text)
updateMaintenanceWindow_scheduleTimezone :: Lens' UpdateMaintenanceWindow (Maybe Text)
updateMaintenanceWindow_scheduleTimezone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe Text
scheduleTimezone :: Maybe Text
$sel:scheduleTimezone:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
scheduleTimezone} -> Maybe Text
scheduleTimezone) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe Text
a -> UpdateMaintenanceWindow
s {$sel:scheduleTimezone:UpdateMaintenanceWindow' :: Maybe Text
scheduleTimezone = Maybe Text
a} :: UpdateMaintenanceWindow)

-- | The date and time, in ISO-8601 Extended format, for when you want the
-- maintenance window to become active. @StartDate@ allows you to delay
-- activation of the maintenance window until the specified future date.
updateMaintenanceWindow_startDate :: Lens.Lens' UpdateMaintenanceWindow (Prelude.Maybe Prelude.Text)
updateMaintenanceWindow_startDate :: Lens' UpdateMaintenanceWindow (Maybe Text)
updateMaintenanceWindow_startDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Maybe Text
startDate :: Maybe Text
$sel:startDate:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
startDate} -> Maybe Text
startDate) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Maybe Text
a -> UpdateMaintenanceWindow
s {$sel:startDate:UpdateMaintenanceWindow' :: Maybe Text
startDate = Maybe Text
a} :: UpdateMaintenanceWindow)

-- | The ID of the maintenance window to update.
updateMaintenanceWindow_windowId :: Lens.Lens' UpdateMaintenanceWindow Prelude.Text
updateMaintenanceWindow_windowId :: Lens' UpdateMaintenanceWindow Text
updateMaintenanceWindow_windowId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindow' {Text
windowId :: Text
$sel:windowId:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Text
windowId} -> Text
windowId) (\s :: UpdateMaintenanceWindow
s@UpdateMaintenanceWindow' {} Text
a -> UpdateMaintenanceWindow
s {$sel:windowId:UpdateMaintenanceWindow' :: Text
windowId = Text
a} :: UpdateMaintenanceWindow)

instance Core.AWSRequest UpdateMaintenanceWindow where
  type
    AWSResponse UpdateMaintenanceWindow =
      UpdateMaintenanceWindowResponse
  request :: (Service -> Service)
-> UpdateMaintenanceWindow -> Request UpdateMaintenanceWindow
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateMaintenanceWindow
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateMaintenanceWindow)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Bool
-> Maybe Natural
-> Maybe (Sensitive Text)
-> Maybe Natural
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> UpdateMaintenanceWindowResponse
UpdateMaintenanceWindowResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"AllowUnassociatedTargets")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Cutoff")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Duration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Enabled")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"EndDate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Schedule")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ScheduleOffset")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ScheduleTimezone")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"StartDate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"WindowId")
            forall (f :: * -> *) a b. Applicative f => 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 UpdateMaintenanceWindow where
  hashWithSalt :: Int -> UpdateMaintenanceWindow -> Int
hashWithSalt Int
_salt UpdateMaintenanceWindow' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
windowId :: Text
startDate :: Maybe Text
scheduleTimezone :: Maybe Text
scheduleOffset :: Maybe Natural
schedule :: Maybe Text
replace :: Maybe Bool
name :: Maybe Text
endDate :: Maybe Text
enabled :: Maybe Bool
duration :: Maybe Natural
description :: Maybe (Sensitive Text)
cutoff :: Maybe Natural
allowUnassociatedTargets :: Maybe Bool
$sel:windowId:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Text
$sel:startDate:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:scheduleTimezone:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:scheduleOffset:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
$sel:schedule:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:replace:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
$sel:name:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:endDate:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:enabled:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
$sel:duration:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
$sel:description:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe (Sensitive Text)
$sel:cutoff:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
$sel:allowUnassociatedTargets:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
allowUnassociatedTargets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
cutoff
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
duration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
endDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
replace
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
schedule
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
scheduleOffset
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
scheduleTimezone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
startDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
windowId

instance Prelude.NFData UpdateMaintenanceWindow where
  rnf :: UpdateMaintenanceWindow -> ()
rnf UpdateMaintenanceWindow' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
windowId :: Text
startDate :: Maybe Text
scheduleTimezone :: Maybe Text
scheduleOffset :: Maybe Natural
schedule :: Maybe Text
replace :: Maybe Bool
name :: Maybe Text
endDate :: Maybe Text
enabled :: Maybe Bool
duration :: Maybe Natural
description :: Maybe (Sensitive Text)
cutoff :: Maybe Natural
allowUnassociatedTargets :: Maybe Bool
$sel:windowId:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Text
$sel:startDate:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:scheduleTimezone:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:scheduleOffset:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
$sel:schedule:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:replace:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
$sel:name:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:endDate:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:enabled:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
$sel:duration:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
$sel:description:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe (Sensitive Text)
$sel:cutoff:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
$sel:allowUnassociatedTargets:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
allowUnassociatedTargets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
cutoff
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
duration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
replace
      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 Natural
scheduleOffset
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
scheduleTimezone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
startDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
windowId

instance Data.ToHeaders UpdateMaintenanceWindow where
  toHeaders :: UpdateMaintenanceWindow -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AmazonSSM.UpdateMaintenanceWindow" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateMaintenanceWindow where
  toJSON :: UpdateMaintenanceWindow -> Value
toJSON UpdateMaintenanceWindow' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
windowId :: Text
startDate :: Maybe Text
scheduleTimezone :: Maybe Text
scheduleOffset :: Maybe Natural
schedule :: Maybe Text
replace :: Maybe Bool
name :: Maybe Text
endDate :: Maybe Text
enabled :: Maybe Bool
duration :: Maybe Natural
description :: Maybe (Sensitive Text)
cutoff :: Maybe Natural
allowUnassociatedTargets :: Maybe Bool
$sel:windowId:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Text
$sel:startDate:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:scheduleTimezone:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:scheduleOffset:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
$sel:schedule:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:replace:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
$sel:name:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:endDate:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Text
$sel:enabled:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
$sel:duration:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
$sel:description:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe (Sensitive Text)
$sel:cutoff:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Natural
$sel:allowUnassociatedTargets:UpdateMaintenanceWindow' :: UpdateMaintenanceWindow -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AllowUnassociatedTargets" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
allowUnassociatedTargets,
            (Key
"Cutoff" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
cutoff,
            (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive Text)
description,
            (Key
"Duration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
duration,
            (Key
"Enabled" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
enabled,
            (Key
"EndDate" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
endDate,
            (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
name,
            (Key
"Replace" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
replace,
            (Key
"Schedule" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
schedule,
            (Key
"ScheduleOffset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
scheduleOffset,
            (Key
"ScheduleTimezone" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
scheduleTimezone,
            (Key
"StartDate" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
startDate,
            forall a. a -> Maybe a
Prelude.Just (Key
"WindowId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
windowId)
          ]
      )

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

instance Data.ToQuery UpdateMaintenanceWindow where
  toQuery :: UpdateMaintenanceWindow -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateMaintenanceWindowResponse' smart constructor.
data UpdateMaintenanceWindowResponse = UpdateMaintenanceWindowResponse'
  { -- | Whether targets must be registered with the maintenance window before
    -- tasks can be defined for those targets.
    UpdateMaintenanceWindowResponse -> Maybe Bool
allowUnassociatedTargets :: Prelude.Maybe Prelude.Bool,
    -- | The number of hours before the end of the maintenance window that Amazon
    -- Web Services Systems Manager stops scheduling new tasks for execution.
    UpdateMaintenanceWindowResponse -> Maybe Natural
cutoff :: Prelude.Maybe Prelude.Natural,
    -- | An optional description of the update.
    UpdateMaintenanceWindowResponse -> Maybe (Sensitive Text)
description :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The duration of the maintenance window in hours.
    UpdateMaintenanceWindowResponse -> Maybe Natural
duration :: Prelude.Maybe Prelude.Natural,
    -- | Whether the maintenance window is enabled.
    UpdateMaintenanceWindowResponse -> Maybe Bool
enabled :: Prelude.Maybe Prelude.Bool,
    -- | The date and time, in ISO-8601 Extended format, for when the maintenance
    -- window is scheduled to become inactive. The maintenance window won\'t
    -- run after this specified time.
    UpdateMaintenanceWindowResponse -> Maybe Text
endDate :: Prelude.Maybe Prelude.Text,
    -- | The name of the maintenance window.
    UpdateMaintenanceWindowResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The schedule of the maintenance window in the form of a cron or rate
    -- expression.
    UpdateMaintenanceWindowResponse -> Maybe Text
schedule :: Prelude.Maybe Prelude.Text,
    -- | The number of days to wait to run a maintenance window after the
    -- scheduled cron expression date and time.
    UpdateMaintenanceWindowResponse -> Maybe Natural
scheduleOffset :: Prelude.Maybe Prelude.Natural,
    -- | The time zone that the scheduled maintenance window executions are based
    -- on, in Internet Assigned Numbers Authority (IANA) format. For example:
    -- \"America\/Los_Angeles\", \"UTC\", or \"Asia\/Seoul\". For more
    -- information, see the
    -- <https://www.iana.org/time-zones Time Zone Database> on the IANA
    -- website.
    UpdateMaintenanceWindowResponse -> Maybe Text
scheduleTimezone :: Prelude.Maybe Prelude.Text,
    -- | The date and time, in ISO-8601 Extended format, for when the maintenance
    -- window is scheduled to become active. The maintenance window won\'t run
    -- before this specified time.
    UpdateMaintenanceWindowResponse -> Maybe Text
startDate :: Prelude.Maybe Prelude.Text,
    -- | The ID of the created maintenance window.
    UpdateMaintenanceWindowResponse -> Maybe Text
windowId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateMaintenanceWindowResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateMaintenanceWindowResponse
-> UpdateMaintenanceWindowResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateMaintenanceWindowResponse
-> UpdateMaintenanceWindowResponse -> Bool
$c/= :: UpdateMaintenanceWindowResponse
-> UpdateMaintenanceWindowResponse -> Bool
== :: UpdateMaintenanceWindowResponse
-> UpdateMaintenanceWindowResponse -> Bool
$c== :: UpdateMaintenanceWindowResponse
-> UpdateMaintenanceWindowResponse -> Bool
Prelude.Eq, Int -> UpdateMaintenanceWindowResponse -> ShowS
[UpdateMaintenanceWindowResponse] -> ShowS
UpdateMaintenanceWindowResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateMaintenanceWindowResponse] -> ShowS
$cshowList :: [UpdateMaintenanceWindowResponse] -> ShowS
show :: UpdateMaintenanceWindowResponse -> String
$cshow :: UpdateMaintenanceWindowResponse -> String
showsPrec :: Int -> UpdateMaintenanceWindowResponse -> ShowS
$cshowsPrec :: Int -> UpdateMaintenanceWindowResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateMaintenanceWindowResponse x
-> UpdateMaintenanceWindowResponse
forall x.
UpdateMaintenanceWindowResponse
-> Rep UpdateMaintenanceWindowResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateMaintenanceWindowResponse x
-> UpdateMaintenanceWindowResponse
$cfrom :: forall x.
UpdateMaintenanceWindowResponse
-> Rep UpdateMaintenanceWindowResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateMaintenanceWindowResponse' 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:
--
-- 'allowUnassociatedTargets', 'updateMaintenanceWindowResponse_allowUnassociatedTargets' - Whether targets must be registered with the maintenance window before
-- tasks can be defined for those targets.
--
-- 'cutoff', 'updateMaintenanceWindowResponse_cutoff' - The number of hours before the end of the maintenance window that Amazon
-- Web Services Systems Manager stops scheduling new tasks for execution.
--
-- 'description', 'updateMaintenanceWindowResponse_description' - An optional description of the update.
--
-- 'duration', 'updateMaintenanceWindowResponse_duration' - The duration of the maintenance window in hours.
--
-- 'enabled', 'updateMaintenanceWindowResponse_enabled' - Whether the maintenance window is enabled.
--
-- 'endDate', 'updateMaintenanceWindowResponse_endDate' - The date and time, in ISO-8601 Extended format, for when the maintenance
-- window is scheduled to become inactive. The maintenance window won\'t
-- run after this specified time.
--
-- 'name', 'updateMaintenanceWindowResponse_name' - The name of the maintenance window.
--
-- 'schedule', 'updateMaintenanceWindowResponse_schedule' - The schedule of the maintenance window in the form of a cron or rate
-- expression.
--
-- 'scheduleOffset', 'updateMaintenanceWindowResponse_scheduleOffset' - The number of days to wait to run a maintenance window after the
-- scheduled cron expression date and time.
--
-- 'scheduleTimezone', 'updateMaintenanceWindowResponse_scheduleTimezone' - The time zone that the scheduled maintenance window executions are based
-- on, in Internet Assigned Numbers Authority (IANA) format. For example:
-- \"America\/Los_Angeles\", \"UTC\", or \"Asia\/Seoul\". For more
-- information, see the
-- <https://www.iana.org/time-zones Time Zone Database> on the IANA
-- website.
--
-- 'startDate', 'updateMaintenanceWindowResponse_startDate' - The date and time, in ISO-8601 Extended format, for when the maintenance
-- window is scheduled to become active. The maintenance window won\'t run
-- before this specified time.
--
-- 'windowId', 'updateMaintenanceWindowResponse_windowId' - The ID of the created maintenance window.
--
-- 'httpStatus', 'updateMaintenanceWindowResponse_httpStatus' - The response's http status code.
newUpdateMaintenanceWindowResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateMaintenanceWindowResponse
newUpdateMaintenanceWindowResponse :: Int -> UpdateMaintenanceWindowResponse
newUpdateMaintenanceWindowResponse Int
pHttpStatus_ =
  UpdateMaintenanceWindowResponse'
    { $sel:allowUnassociatedTargets:UpdateMaintenanceWindowResponse' :: Maybe Bool
allowUnassociatedTargets =
        forall a. Maybe a
Prelude.Nothing,
      $sel:cutoff:UpdateMaintenanceWindowResponse' :: Maybe Natural
cutoff = forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateMaintenanceWindowResponse' :: Maybe (Sensitive Text)
description = forall a. Maybe a
Prelude.Nothing,
      $sel:duration:UpdateMaintenanceWindowResponse' :: Maybe Natural
duration = forall a. Maybe a
Prelude.Nothing,
      $sel:enabled:UpdateMaintenanceWindowResponse' :: Maybe Bool
enabled = forall a. Maybe a
Prelude.Nothing,
      $sel:endDate:UpdateMaintenanceWindowResponse' :: Maybe Text
endDate = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateMaintenanceWindowResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:schedule:UpdateMaintenanceWindowResponse' :: Maybe Text
schedule = forall a. Maybe a
Prelude.Nothing,
      $sel:scheduleOffset:UpdateMaintenanceWindowResponse' :: Maybe Natural
scheduleOffset = forall a. Maybe a
Prelude.Nothing,
      $sel:scheduleTimezone:UpdateMaintenanceWindowResponse' :: Maybe Text
scheduleTimezone = forall a. Maybe a
Prelude.Nothing,
      $sel:startDate:UpdateMaintenanceWindowResponse' :: Maybe Text
startDate = forall a. Maybe a
Prelude.Nothing,
      $sel:windowId:UpdateMaintenanceWindowResponse' :: Maybe Text
windowId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateMaintenanceWindowResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Whether targets must be registered with the maintenance window before
-- tasks can be defined for those targets.
updateMaintenanceWindowResponse_allowUnassociatedTargets :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Bool)
updateMaintenanceWindowResponse_allowUnassociatedTargets :: Lens' UpdateMaintenanceWindowResponse (Maybe Bool)
updateMaintenanceWindowResponse_allowUnassociatedTargets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe Bool
allowUnassociatedTargets :: Maybe Bool
$sel:allowUnassociatedTargets:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Bool
allowUnassociatedTargets} -> Maybe Bool
allowUnassociatedTargets) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe Bool
a -> UpdateMaintenanceWindowResponse
s {$sel:allowUnassociatedTargets:UpdateMaintenanceWindowResponse' :: Maybe Bool
allowUnassociatedTargets = Maybe Bool
a} :: UpdateMaintenanceWindowResponse)

-- | The number of hours before the end of the maintenance window that Amazon
-- Web Services Systems Manager stops scheduling new tasks for execution.
updateMaintenanceWindowResponse_cutoff :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Natural)
updateMaintenanceWindowResponse_cutoff :: Lens' UpdateMaintenanceWindowResponse (Maybe Natural)
updateMaintenanceWindowResponse_cutoff = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe Natural
cutoff :: Maybe Natural
$sel:cutoff:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Natural
cutoff} -> Maybe Natural
cutoff) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe Natural
a -> UpdateMaintenanceWindowResponse
s {$sel:cutoff:UpdateMaintenanceWindowResponse' :: Maybe Natural
cutoff = Maybe Natural
a} :: UpdateMaintenanceWindowResponse)

-- | An optional description of the update.
updateMaintenanceWindowResponse_description :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowResponse_description :: Lens' UpdateMaintenanceWindowResponse (Maybe Text)
updateMaintenanceWindowResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:description:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe (Sensitive Text)
description} -> Maybe (Sensitive Text)
description) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe (Sensitive Text)
a -> UpdateMaintenanceWindowResponse
s {$sel:description:UpdateMaintenanceWindowResponse' :: Maybe (Sensitive Text)
description = Maybe (Sensitive Text)
a} :: UpdateMaintenanceWindowResponse) 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. Iso' (Sensitive a) a
Data._Sensitive

-- | The duration of the maintenance window in hours.
updateMaintenanceWindowResponse_duration :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Natural)
updateMaintenanceWindowResponse_duration :: Lens' UpdateMaintenanceWindowResponse (Maybe Natural)
updateMaintenanceWindowResponse_duration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe Natural
duration :: Maybe Natural
$sel:duration:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Natural
duration} -> Maybe Natural
duration) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe Natural
a -> UpdateMaintenanceWindowResponse
s {$sel:duration:UpdateMaintenanceWindowResponse' :: Maybe Natural
duration = Maybe Natural
a} :: UpdateMaintenanceWindowResponse)

-- | Whether the maintenance window is enabled.
updateMaintenanceWindowResponse_enabled :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Bool)
updateMaintenanceWindowResponse_enabled :: Lens' UpdateMaintenanceWindowResponse (Maybe Bool)
updateMaintenanceWindowResponse_enabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe Bool
enabled :: Maybe Bool
$sel:enabled:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Bool
enabled} -> Maybe Bool
enabled) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe Bool
a -> UpdateMaintenanceWindowResponse
s {$sel:enabled:UpdateMaintenanceWindowResponse' :: Maybe Bool
enabled = Maybe Bool
a} :: UpdateMaintenanceWindowResponse)

-- | The date and time, in ISO-8601 Extended format, for when the maintenance
-- window is scheduled to become inactive. The maintenance window won\'t
-- run after this specified time.
updateMaintenanceWindowResponse_endDate :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowResponse_endDate :: Lens' UpdateMaintenanceWindowResponse (Maybe Text)
updateMaintenanceWindowResponse_endDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe Text
endDate :: Maybe Text
$sel:endDate:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
endDate} -> Maybe Text
endDate) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe Text
a -> UpdateMaintenanceWindowResponse
s {$sel:endDate:UpdateMaintenanceWindowResponse' :: Maybe Text
endDate = Maybe Text
a} :: UpdateMaintenanceWindowResponse)

-- | The name of the maintenance window.
updateMaintenanceWindowResponse_name :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowResponse_name :: Lens' UpdateMaintenanceWindowResponse (Maybe Text)
updateMaintenanceWindowResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe Text
name :: Maybe Text
$sel:name:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe Text
a -> UpdateMaintenanceWindowResponse
s {$sel:name:UpdateMaintenanceWindowResponse' :: Maybe Text
name = Maybe Text
a} :: UpdateMaintenanceWindowResponse)

-- | The schedule of the maintenance window in the form of a cron or rate
-- expression.
updateMaintenanceWindowResponse_schedule :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowResponse_schedule :: Lens' UpdateMaintenanceWindowResponse (Maybe Text)
updateMaintenanceWindowResponse_schedule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe Text
schedule :: Maybe Text
$sel:schedule:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
schedule} -> Maybe Text
schedule) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe Text
a -> UpdateMaintenanceWindowResponse
s {$sel:schedule:UpdateMaintenanceWindowResponse' :: Maybe Text
schedule = Maybe Text
a} :: UpdateMaintenanceWindowResponse)

-- | The number of days to wait to run a maintenance window after the
-- scheduled cron expression date and time.
updateMaintenanceWindowResponse_scheduleOffset :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Natural)
updateMaintenanceWindowResponse_scheduleOffset :: Lens' UpdateMaintenanceWindowResponse (Maybe Natural)
updateMaintenanceWindowResponse_scheduleOffset = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe Natural
scheduleOffset :: Maybe Natural
$sel:scheduleOffset:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Natural
scheduleOffset} -> Maybe Natural
scheduleOffset) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe Natural
a -> UpdateMaintenanceWindowResponse
s {$sel:scheduleOffset:UpdateMaintenanceWindowResponse' :: Maybe Natural
scheduleOffset = Maybe Natural
a} :: UpdateMaintenanceWindowResponse)

-- | The time zone that the scheduled maintenance window executions are based
-- on, in Internet Assigned Numbers Authority (IANA) format. For example:
-- \"America\/Los_Angeles\", \"UTC\", or \"Asia\/Seoul\". For more
-- information, see the
-- <https://www.iana.org/time-zones Time Zone Database> on the IANA
-- website.
updateMaintenanceWindowResponse_scheduleTimezone :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowResponse_scheduleTimezone :: Lens' UpdateMaintenanceWindowResponse (Maybe Text)
updateMaintenanceWindowResponse_scheduleTimezone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe Text
scheduleTimezone :: Maybe Text
$sel:scheduleTimezone:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
scheduleTimezone} -> Maybe Text
scheduleTimezone) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe Text
a -> UpdateMaintenanceWindowResponse
s {$sel:scheduleTimezone:UpdateMaintenanceWindowResponse' :: Maybe Text
scheduleTimezone = Maybe Text
a} :: UpdateMaintenanceWindowResponse)

-- | The date and time, in ISO-8601 Extended format, for when the maintenance
-- window is scheduled to become active. The maintenance window won\'t run
-- before this specified time.
updateMaintenanceWindowResponse_startDate :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowResponse_startDate :: Lens' UpdateMaintenanceWindowResponse (Maybe Text)
updateMaintenanceWindowResponse_startDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe Text
startDate :: Maybe Text
$sel:startDate:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
startDate} -> Maybe Text
startDate) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe Text
a -> UpdateMaintenanceWindowResponse
s {$sel:startDate:UpdateMaintenanceWindowResponse' :: Maybe Text
startDate = Maybe Text
a} :: UpdateMaintenanceWindowResponse)

-- | The ID of the created maintenance window.
updateMaintenanceWindowResponse_windowId :: Lens.Lens' UpdateMaintenanceWindowResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowResponse_windowId :: Lens' UpdateMaintenanceWindowResponse (Maybe Text)
updateMaintenanceWindowResponse_windowId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowResponse' {Maybe Text
windowId :: Maybe Text
$sel:windowId:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
windowId} -> Maybe Text
windowId) (\s :: UpdateMaintenanceWindowResponse
s@UpdateMaintenanceWindowResponse' {} Maybe Text
a -> UpdateMaintenanceWindowResponse
s {$sel:windowId:UpdateMaintenanceWindowResponse' :: Maybe Text
windowId = Maybe Text
a} :: UpdateMaintenanceWindowResponse)

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

instance
  Prelude.NFData
    UpdateMaintenanceWindowResponse
  where
  rnf :: UpdateMaintenanceWindowResponse -> ()
rnf UpdateMaintenanceWindowResponse' {Int
Maybe Bool
Maybe Natural
Maybe Text
Maybe (Sensitive Text)
httpStatus :: Int
windowId :: Maybe Text
startDate :: Maybe Text
scheduleTimezone :: Maybe Text
scheduleOffset :: Maybe Natural
schedule :: Maybe Text
name :: Maybe Text
endDate :: Maybe Text
enabled :: Maybe Bool
duration :: Maybe Natural
description :: Maybe (Sensitive Text)
cutoff :: Maybe Natural
allowUnassociatedTargets :: Maybe Bool
$sel:httpStatus:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Int
$sel:windowId:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
$sel:startDate:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
$sel:scheduleTimezone:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
$sel:scheduleOffset:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Natural
$sel:schedule:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
$sel:name:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
$sel:endDate:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Text
$sel:enabled:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Bool
$sel:duration:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Natural
$sel:description:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe (Sensitive Text)
$sel:cutoff:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Natural
$sel:allowUnassociatedTargets:UpdateMaintenanceWindowResponse' :: UpdateMaintenanceWindowResponse -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
allowUnassociatedTargets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
cutoff
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
duration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      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 Natural
scheduleOffset
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
scheduleTimezone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
startDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
windowId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus