{-# 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.UpdateMaintenanceWindowTask
-- 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 task assigned to a maintenance window. You can\'t change the
-- task type, but you can change the following values:
--
-- -   @TaskARN@. For example, you can change a @RUN_COMMAND@ task from
--     @AWS-RunPowerShellScript@ to @AWS-RunShellScript@.
--
-- -   @ServiceRoleArn@
--
-- -   @TaskInvocationParameters@
--
-- -   @Priority@
--
-- -   @MaxConcurrency@
--
-- -   @MaxErrors@
--
-- One or more targets must be specified for maintenance window Run
-- Command-type tasks. Depending on the task, targets are optional for
-- other maintenance window task types (Automation, Lambda, and Step
-- Functions). For more information about running tasks that don\'t specify
-- targets, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/maintenance-windows-targetless-tasks.html Registering maintenance window tasks without targets>
-- in the /Amazon Web Services Systems Manager User Guide/.
--
-- If the value for a parameter in @UpdateMaintenanceWindowTask@ is null,
-- then the corresponding field isn\'t modified. If you set @Replace@ to
-- true, then all fields required by the RegisterTaskWithMaintenanceWindow
-- operation are required for this request. Optional fields that aren\'t
-- specified are set to null.
--
-- When you update a maintenance window task that has options specified in
-- @TaskInvocationParameters@, you must provide again all the
-- @TaskInvocationParameters@ values that you want to retain. The values
-- you don\'t specify again are removed. For example, suppose that when you
-- registered a Run Command task, you specified @TaskInvocationParameters@
-- values for @Comment@, @NotificationConfig@, and @OutputS3BucketName@. If
-- you update the maintenance window task and specify only a different
-- @OutputS3BucketName@ value, the values for @Comment@ and
-- @NotificationConfig@ are removed.
module Amazonka.SSM.UpdateMaintenanceWindowTask
  ( -- * Creating a Request
    UpdateMaintenanceWindowTask (..),
    newUpdateMaintenanceWindowTask,

    -- * Request Lenses
    updateMaintenanceWindowTask_alarmConfiguration,
    updateMaintenanceWindowTask_cutoffBehavior,
    updateMaintenanceWindowTask_description,
    updateMaintenanceWindowTask_loggingInfo,
    updateMaintenanceWindowTask_maxConcurrency,
    updateMaintenanceWindowTask_maxErrors,
    updateMaintenanceWindowTask_name,
    updateMaintenanceWindowTask_priority,
    updateMaintenanceWindowTask_replace,
    updateMaintenanceWindowTask_serviceRoleArn,
    updateMaintenanceWindowTask_targets,
    updateMaintenanceWindowTask_taskArn,
    updateMaintenanceWindowTask_taskInvocationParameters,
    updateMaintenanceWindowTask_taskParameters,
    updateMaintenanceWindowTask_windowId,
    updateMaintenanceWindowTask_windowTaskId,

    -- * Destructuring the Response
    UpdateMaintenanceWindowTaskResponse (..),
    newUpdateMaintenanceWindowTaskResponse,

    -- * Response Lenses
    updateMaintenanceWindowTaskResponse_alarmConfiguration,
    updateMaintenanceWindowTaskResponse_cutoffBehavior,
    updateMaintenanceWindowTaskResponse_description,
    updateMaintenanceWindowTaskResponse_loggingInfo,
    updateMaintenanceWindowTaskResponse_maxConcurrency,
    updateMaintenanceWindowTaskResponse_maxErrors,
    updateMaintenanceWindowTaskResponse_name,
    updateMaintenanceWindowTaskResponse_priority,
    updateMaintenanceWindowTaskResponse_serviceRoleArn,
    updateMaintenanceWindowTaskResponse_targets,
    updateMaintenanceWindowTaskResponse_taskArn,
    updateMaintenanceWindowTaskResponse_taskInvocationParameters,
    updateMaintenanceWindowTaskResponse_taskParameters,
    updateMaintenanceWindowTaskResponse_windowId,
    updateMaintenanceWindowTaskResponse_windowTaskId,
    updateMaintenanceWindowTaskResponse_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:/ 'newUpdateMaintenanceWindowTask' smart constructor.
data UpdateMaintenanceWindowTask = UpdateMaintenanceWindowTask'
  { -- | The CloudWatch alarm you want to apply to your maintenance window task.
    UpdateMaintenanceWindowTask -> Maybe AlarmConfiguration
alarmConfiguration :: Prelude.Maybe AlarmConfiguration,
    -- | Indicates whether tasks should continue to run after the cutoff time
    -- specified in the maintenance windows is reached.
    --
    -- -   @CONTINUE_TASK@: When the cutoff time is reached, any tasks that are
    --     running continue. The default value.
    --
    -- -   @CANCEL_TASK@:
    --
    --     -   For Automation, Lambda, Step Functions tasks: When the cutoff
    --         time is reached, any task invocations that are already running
    --         continue, but no new task invocations are started.
    --
    --     -   For Run Command tasks: When the cutoff time is reached, the
    --         system sends a CancelCommand operation that attempts to cancel
    --         the command associated with the task. However, there is no
    --         guarantee that the command will be terminated and the underlying
    --         process stopped.
    --
    --     The status for tasks that are not completed is @TIMED_OUT@.
    UpdateMaintenanceWindowTask
-> Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior :: Prelude.Maybe MaintenanceWindowTaskCutoffBehavior,
    -- | The new task description to specify.
    UpdateMaintenanceWindowTask -> Maybe (Sensitive Text)
description :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The new logging location in Amazon S3 to specify.
    --
    -- @LoggingInfo@ has been deprecated. To specify an Amazon Simple Storage
    -- Service (Amazon S3) bucket to contain logs, instead use the
    -- @OutputS3BucketName@ and @OutputS3KeyPrefix@ options in the
    -- @TaskInvocationParameters@ structure. For information about how Amazon
    -- Web Services Systems Manager handles these options for the supported
    -- maintenance window task types, see
    -- MaintenanceWindowTaskInvocationParameters.
    UpdateMaintenanceWindowTask -> Maybe LoggingInfo
loggingInfo :: Prelude.Maybe LoggingInfo,
    -- | The new @MaxConcurrency@ value you want to specify. @MaxConcurrency@ is
    -- the number of targets that are allowed to run this task, in parallel.
    --
    -- Although this element is listed as \"Required: No\", a value can be
    -- omitted only when you are registering or updating a
    -- <https://docs.aws.amazon.com/systems-manager/latest/userguide/maintenance-windows-targetless-tasks.html targetless task>
    -- You must provide a value in all other cases.
    --
    -- For maintenance window tasks without a target specified, you can\'t
    -- supply a value for this option. Instead, the system inserts a
    -- placeholder value of @1@. This value doesn\'t affect the running of your
    -- task.
    UpdateMaintenanceWindowTask -> Maybe Text
maxConcurrency :: Prelude.Maybe Prelude.Text,
    -- | The new @MaxErrors@ value to specify. @MaxErrors@ is the maximum number
    -- of errors that are allowed before the task stops being scheduled.
    --
    -- Although this element is listed as \"Required: No\", a value can be
    -- omitted only when you are registering or updating a
    -- <https://docs.aws.amazon.com/systems-manager/latest/userguide/maintenance-windows-targetless-tasks.html targetless task>
    -- You must provide a value in all other cases.
    --
    -- For maintenance window tasks without a target specified, you can\'t
    -- supply a value for this option. Instead, the system inserts a
    -- placeholder value of @1@. This value doesn\'t affect the running of your
    -- task.
    UpdateMaintenanceWindowTask -> Maybe Text
maxErrors :: Prelude.Maybe Prelude.Text,
    -- | The new task name to specify.
    UpdateMaintenanceWindowTask -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The new task priority to specify. The lower the number, the higher the
    -- priority. Tasks that have the same priority are scheduled in parallel.
    UpdateMaintenanceWindowTask -> Maybe Natural
priority :: Prelude.Maybe Prelude.Natural,
    -- | If True, then all fields that are required by the
    -- RegisterTaskWithMaintenanceWindow operation are also required for this
    -- API request. Optional fields that aren\'t specified are set to null.
    UpdateMaintenanceWindowTask -> Maybe Bool
replace :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) of the IAM service role for Amazon Web
    -- Services Systems Manager to assume when running a maintenance window
    -- task. If you do not specify a service role ARN, Systems Manager uses
    -- your account\'s service-linked role. If no service-linked role for
    -- Systems Manager exists in your account, it is created when you run
    -- @RegisterTaskWithMaintenanceWindow@.
    --
    -- For more information, see the following topics in the in the /Amazon Web
    -- Services Systems Manager User Guide/:
    --
    -- -   <https://docs.aws.amazon.com/systems-manager/latest/userguide/using-service-linked-roles.html#slr-permissions Using service-linked roles for Systems Manager>
    --
    -- -   <https://docs.aws.amazon.com/systems-manager/latest/userguide/sysman-maintenance-permissions.html#maintenance-window-tasks-service-role Should I use a service-linked role or a custom service role to run maintenance window tasks?>
    UpdateMaintenanceWindowTask -> Maybe Text
serviceRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The targets (either managed nodes or tags) to modify. Managed nodes are
    -- specified using the format
    -- @Key=instanceids,Values=instanceID_1,instanceID_2@. Tags are specified
    -- using the format @ Key=tag_name,Values=tag_value@.
    --
    -- One or more targets must be specified for maintenance window Run
    -- Command-type tasks. Depending on the task, targets are optional for
    -- other maintenance window task types (Automation, Lambda, and Step
    -- Functions). For more information about running tasks that don\'t specify
    -- targets, see
    -- <https://docs.aws.amazon.com/systems-manager/latest/userguide/maintenance-windows-targetless-tasks.html Registering maintenance window tasks without targets>
    -- in the /Amazon Web Services Systems Manager User Guide/.
    UpdateMaintenanceWindowTask -> Maybe [Target]
targets :: Prelude.Maybe [Target],
    -- | The task ARN to modify.
    UpdateMaintenanceWindowTask -> Maybe Text
taskArn :: Prelude.Maybe Prelude.Text,
    -- | The parameters that the task should use during execution. Populate only
    -- the fields that match the task type. All other fields should be empty.
    --
    -- When you update a maintenance window task that has options specified in
    -- @TaskInvocationParameters@, you must provide again all the
    -- @TaskInvocationParameters@ values that you want to retain. The values
    -- you don\'t specify again are removed. For example, suppose that when you
    -- registered a Run Command task, you specified @TaskInvocationParameters@
    -- values for @Comment@, @NotificationConfig@, and @OutputS3BucketName@. If
    -- you update the maintenance window task and specify only a different
    -- @OutputS3BucketName@ value, the values for @Comment@ and
    -- @NotificationConfig@ are removed.
    UpdateMaintenanceWindowTask
-> Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters :: Prelude.Maybe MaintenanceWindowTaskInvocationParameters,
    -- | The parameters to modify.
    --
    -- @TaskParameters@ has been deprecated. To specify parameters to pass to a
    -- task when it runs, instead use the @Parameters@ option in the
    -- @TaskInvocationParameters@ structure. For information about how Systems
    -- Manager handles these options for the supported maintenance window task
    -- types, see MaintenanceWindowTaskInvocationParameters.
    --
    -- The map has the following format:
    --
    -- Key: string, between 1 and 255 characters
    --
    -- Value: an array of strings, each string is between 1 and 255 characters
    UpdateMaintenanceWindowTask
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text (Data.Sensitive MaintenanceWindowTaskParameterValueExpression))),
    -- | The maintenance window ID that contains the task to modify.
    UpdateMaintenanceWindowTask -> Text
windowId :: Prelude.Text,
    -- | The task ID to modify.
    UpdateMaintenanceWindowTask -> Text
windowTaskId :: Prelude.Text
  }
  deriving (UpdateMaintenanceWindowTask -> UpdateMaintenanceWindowTask -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateMaintenanceWindowTask -> UpdateMaintenanceWindowTask -> Bool
$c/= :: UpdateMaintenanceWindowTask -> UpdateMaintenanceWindowTask -> Bool
== :: UpdateMaintenanceWindowTask -> UpdateMaintenanceWindowTask -> Bool
$c== :: UpdateMaintenanceWindowTask -> UpdateMaintenanceWindowTask -> Bool
Prelude.Eq, Int -> UpdateMaintenanceWindowTask -> ShowS
[UpdateMaintenanceWindowTask] -> ShowS
UpdateMaintenanceWindowTask -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateMaintenanceWindowTask] -> ShowS
$cshowList :: [UpdateMaintenanceWindowTask] -> ShowS
show :: UpdateMaintenanceWindowTask -> String
$cshow :: UpdateMaintenanceWindowTask -> String
showsPrec :: Int -> UpdateMaintenanceWindowTask -> ShowS
$cshowsPrec :: Int -> UpdateMaintenanceWindowTask -> ShowS
Prelude.Show, forall x.
Rep UpdateMaintenanceWindowTask x -> UpdateMaintenanceWindowTask
forall x.
UpdateMaintenanceWindowTask -> Rep UpdateMaintenanceWindowTask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateMaintenanceWindowTask x -> UpdateMaintenanceWindowTask
$cfrom :: forall x.
UpdateMaintenanceWindowTask -> Rep UpdateMaintenanceWindowTask x
Prelude.Generic)

-- |
-- Create a value of 'UpdateMaintenanceWindowTask' 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:
--
-- 'alarmConfiguration', 'updateMaintenanceWindowTask_alarmConfiguration' - The CloudWatch alarm you want to apply to your maintenance window task.
--
-- 'cutoffBehavior', 'updateMaintenanceWindowTask_cutoffBehavior' - Indicates whether tasks should continue to run after the cutoff time
-- specified in the maintenance windows is reached.
--
-- -   @CONTINUE_TASK@: When the cutoff time is reached, any tasks that are
--     running continue. The default value.
--
-- -   @CANCEL_TASK@:
--
--     -   For Automation, Lambda, Step Functions tasks: When the cutoff
--         time is reached, any task invocations that are already running
--         continue, but no new task invocations are started.
--
--     -   For Run Command tasks: When the cutoff time is reached, the
--         system sends a CancelCommand operation that attempts to cancel
--         the command associated with the task. However, there is no
--         guarantee that the command will be terminated and the underlying
--         process stopped.
--
--     The status for tasks that are not completed is @TIMED_OUT@.
--
-- 'description', 'updateMaintenanceWindowTask_description' - The new task description to specify.
--
-- 'loggingInfo', 'updateMaintenanceWindowTask_loggingInfo' - The new logging location in Amazon S3 to specify.
--
-- @LoggingInfo@ has been deprecated. To specify an Amazon Simple Storage
-- Service (Amazon S3) bucket to contain logs, instead use the
-- @OutputS3BucketName@ and @OutputS3KeyPrefix@ options in the
-- @TaskInvocationParameters@ structure. For information about how Amazon
-- Web Services Systems Manager handles these options for the supported
-- maintenance window task types, see
-- MaintenanceWindowTaskInvocationParameters.
--
-- 'maxConcurrency', 'updateMaintenanceWindowTask_maxConcurrency' - The new @MaxConcurrency@ value you want to specify. @MaxConcurrency@ is
-- the number of targets that are allowed to run this task, in parallel.
--
-- Although this element is listed as \"Required: No\", a value can be
-- omitted only when you are registering or updating a
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/maintenance-windows-targetless-tasks.html targetless task>
-- You must provide a value in all other cases.
--
-- For maintenance window tasks without a target specified, you can\'t
-- supply a value for this option. Instead, the system inserts a
-- placeholder value of @1@. This value doesn\'t affect the running of your
-- task.
--
-- 'maxErrors', 'updateMaintenanceWindowTask_maxErrors' - The new @MaxErrors@ value to specify. @MaxErrors@ is the maximum number
-- of errors that are allowed before the task stops being scheduled.
--
-- Although this element is listed as \"Required: No\", a value can be
-- omitted only when you are registering or updating a
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/maintenance-windows-targetless-tasks.html targetless task>
-- You must provide a value in all other cases.
--
-- For maintenance window tasks without a target specified, you can\'t
-- supply a value for this option. Instead, the system inserts a
-- placeholder value of @1@. This value doesn\'t affect the running of your
-- task.
--
-- 'name', 'updateMaintenanceWindowTask_name' - The new task name to specify.
--
-- 'priority', 'updateMaintenanceWindowTask_priority' - The new task priority to specify. The lower the number, the higher the
-- priority. Tasks that have the same priority are scheduled in parallel.
--
-- 'replace', 'updateMaintenanceWindowTask_replace' - If True, then all fields that are required by the
-- RegisterTaskWithMaintenanceWindow operation are also required for this
-- API request. Optional fields that aren\'t specified are set to null.
--
-- 'serviceRoleArn', 'updateMaintenanceWindowTask_serviceRoleArn' - The Amazon Resource Name (ARN) of the IAM service role for Amazon Web
-- Services Systems Manager to assume when running a maintenance window
-- task. If you do not specify a service role ARN, Systems Manager uses
-- your account\'s service-linked role. If no service-linked role for
-- Systems Manager exists in your account, it is created when you run
-- @RegisterTaskWithMaintenanceWindow@.
--
-- For more information, see the following topics in the in the /Amazon Web
-- Services Systems Manager User Guide/:
--
-- -   <https://docs.aws.amazon.com/systems-manager/latest/userguide/using-service-linked-roles.html#slr-permissions Using service-linked roles for Systems Manager>
--
-- -   <https://docs.aws.amazon.com/systems-manager/latest/userguide/sysman-maintenance-permissions.html#maintenance-window-tasks-service-role Should I use a service-linked role or a custom service role to run maintenance window tasks?>
--
-- 'targets', 'updateMaintenanceWindowTask_targets' - The targets (either managed nodes or tags) to modify. Managed nodes are
-- specified using the format
-- @Key=instanceids,Values=instanceID_1,instanceID_2@. Tags are specified
-- using the format @ Key=tag_name,Values=tag_value@.
--
-- One or more targets must be specified for maintenance window Run
-- Command-type tasks. Depending on the task, targets are optional for
-- other maintenance window task types (Automation, Lambda, and Step
-- Functions). For more information about running tasks that don\'t specify
-- targets, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/maintenance-windows-targetless-tasks.html Registering maintenance window tasks without targets>
-- in the /Amazon Web Services Systems Manager User Guide/.
--
-- 'taskArn', 'updateMaintenanceWindowTask_taskArn' - The task ARN to modify.
--
-- 'taskInvocationParameters', 'updateMaintenanceWindowTask_taskInvocationParameters' - The parameters that the task should use during execution. Populate only
-- the fields that match the task type. All other fields should be empty.
--
-- When you update a maintenance window task that has options specified in
-- @TaskInvocationParameters@, you must provide again all the
-- @TaskInvocationParameters@ values that you want to retain. The values
-- you don\'t specify again are removed. For example, suppose that when you
-- registered a Run Command task, you specified @TaskInvocationParameters@
-- values for @Comment@, @NotificationConfig@, and @OutputS3BucketName@. If
-- you update the maintenance window task and specify only a different
-- @OutputS3BucketName@ value, the values for @Comment@ and
-- @NotificationConfig@ are removed.
--
-- 'taskParameters', 'updateMaintenanceWindowTask_taskParameters' - The parameters to modify.
--
-- @TaskParameters@ has been deprecated. To specify parameters to pass to a
-- task when it runs, instead use the @Parameters@ option in the
-- @TaskInvocationParameters@ structure. For information about how Systems
-- Manager handles these options for the supported maintenance window task
-- types, see MaintenanceWindowTaskInvocationParameters.
--
-- The map has the following format:
--
-- Key: string, between 1 and 255 characters
--
-- Value: an array of strings, each string is between 1 and 255 characters
--
-- 'windowId', 'updateMaintenanceWindowTask_windowId' - The maintenance window ID that contains the task to modify.
--
-- 'windowTaskId', 'updateMaintenanceWindowTask_windowTaskId' - The task ID to modify.
newUpdateMaintenanceWindowTask ::
  -- | 'windowId'
  Prelude.Text ->
  -- | 'windowTaskId'
  Prelude.Text ->
  UpdateMaintenanceWindowTask
newUpdateMaintenanceWindowTask :: Text -> Text -> UpdateMaintenanceWindowTask
newUpdateMaintenanceWindowTask
  Text
pWindowId_
  Text
pWindowTaskId_ =
    UpdateMaintenanceWindowTask'
      { $sel:alarmConfiguration:UpdateMaintenanceWindowTask' :: Maybe AlarmConfiguration
alarmConfiguration =
          forall a. Maybe a
Prelude.Nothing,
        $sel:cutoffBehavior:UpdateMaintenanceWindowTask' :: Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior = forall a. Maybe a
Prelude.Nothing,
        $sel:description:UpdateMaintenanceWindowTask' :: Maybe (Sensitive Text)
description = forall a. Maybe a
Prelude.Nothing,
        $sel:loggingInfo:UpdateMaintenanceWindowTask' :: Maybe LoggingInfo
loggingInfo = forall a. Maybe a
Prelude.Nothing,
        $sel:maxConcurrency:UpdateMaintenanceWindowTask' :: Maybe Text
maxConcurrency = forall a. Maybe a
Prelude.Nothing,
        $sel:maxErrors:UpdateMaintenanceWindowTask' :: Maybe Text
maxErrors = forall a. Maybe a
Prelude.Nothing,
        $sel:name:UpdateMaintenanceWindowTask' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
        $sel:priority:UpdateMaintenanceWindowTask' :: Maybe Natural
priority = forall a. Maybe a
Prelude.Nothing,
        $sel:replace:UpdateMaintenanceWindowTask' :: Maybe Bool
replace = forall a. Maybe a
Prelude.Nothing,
        $sel:serviceRoleArn:UpdateMaintenanceWindowTask' :: Maybe Text
serviceRoleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:targets:UpdateMaintenanceWindowTask' :: Maybe [Target]
targets = forall a. Maybe a
Prelude.Nothing,
        $sel:taskArn:UpdateMaintenanceWindowTask' :: Maybe Text
taskArn = forall a. Maybe a
Prelude.Nothing,
        $sel:taskInvocationParameters:UpdateMaintenanceWindowTask' :: Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters = forall a. Maybe a
Prelude.Nothing,
        $sel:taskParameters:UpdateMaintenanceWindowTask' :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters = forall a. Maybe a
Prelude.Nothing,
        $sel:windowId:UpdateMaintenanceWindowTask' :: Text
windowId = Text
pWindowId_,
        $sel:windowTaskId:UpdateMaintenanceWindowTask' :: Text
windowTaskId = Text
pWindowTaskId_
      }

-- | The CloudWatch alarm you want to apply to your maintenance window task.
updateMaintenanceWindowTask_alarmConfiguration :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe AlarmConfiguration)
updateMaintenanceWindowTask_alarmConfiguration :: Lens' UpdateMaintenanceWindowTask (Maybe AlarmConfiguration)
updateMaintenanceWindowTask_alarmConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe AlarmConfiguration
alarmConfiguration :: Maybe AlarmConfiguration
$sel:alarmConfiguration:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe AlarmConfiguration
alarmConfiguration} -> Maybe AlarmConfiguration
alarmConfiguration) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe AlarmConfiguration
a -> UpdateMaintenanceWindowTask
s {$sel:alarmConfiguration:UpdateMaintenanceWindowTask' :: Maybe AlarmConfiguration
alarmConfiguration = Maybe AlarmConfiguration
a} :: UpdateMaintenanceWindowTask)

-- | Indicates whether tasks should continue to run after the cutoff time
-- specified in the maintenance windows is reached.
--
-- -   @CONTINUE_TASK@: When the cutoff time is reached, any tasks that are
--     running continue. The default value.
--
-- -   @CANCEL_TASK@:
--
--     -   For Automation, Lambda, Step Functions tasks: When the cutoff
--         time is reached, any task invocations that are already running
--         continue, but no new task invocations are started.
--
--     -   For Run Command tasks: When the cutoff time is reached, the
--         system sends a CancelCommand operation that attempts to cancel
--         the command associated with the task. However, there is no
--         guarantee that the command will be terminated and the underlying
--         process stopped.
--
--     The status for tasks that are not completed is @TIMED_OUT@.
updateMaintenanceWindowTask_cutoffBehavior :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe MaintenanceWindowTaskCutoffBehavior)
updateMaintenanceWindowTask_cutoffBehavior :: Lens'
  UpdateMaintenanceWindowTask
  (Maybe MaintenanceWindowTaskCutoffBehavior)
updateMaintenanceWindowTask_cutoffBehavior = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior :: Maybe MaintenanceWindowTaskCutoffBehavior
$sel:cutoffBehavior:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior} -> Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe MaintenanceWindowTaskCutoffBehavior
a -> UpdateMaintenanceWindowTask
s {$sel:cutoffBehavior:UpdateMaintenanceWindowTask' :: Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior = Maybe MaintenanceWindowTaskCutoffBehavior
a} :: UpdateMaintenanceWindowTask)

-- | The new task description to specify.
updateMaintenanceWindowTask_description :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTask_description :: Lens' UpdateMaintenanceWindowTask (Maybe Text)
updateMaintenanceWindowTask_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:description:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe (Sensitive Text)
description} -> Maybe (Sensitive Text)
description) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe (Sensitive Text)
a -> UpdateMaintenanceWindowTask
s {$sel:description:UpdateMaintenanceWindowTask' :: Maybe (Sensitive Text)
description = Maybe (Sensitive Text)
a} :: UpdateMaintenanceWindowTask) 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 new logging location in Amazon S3 to specify.
--
-- @LoggingInfo@ has been deprecated. To specify an Amazon Simple Storage
-- Service (Amazon S3) bucket to contain logs, instead use the
-- @OutputS3BucketName@ and @OutputS3KeyPrefix@ options in the
-- @TaskInvocationParameters@ structure. For information about how Amazon
-- Web Services Systems Manager handles these options for the supported
-- maintenance window task types, see
-- MaintenanceWindowTaskInvocationParameters.
updateMaintenanceWindowTask_loggingInfo :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe LoggingInfo)
updateMaintenanceWindowTask_loggingInfo :: Lens' UpdateMaintenanceWindowTask (Maybe LoggingInfo)
updateMaintenanceWindowTask_loggingInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe LoggingInfo
loggingInfo :: Maybe LoggingInfo
$sel:loggingInfo:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe LoggingInfo
loggingInfo} -> Maybe LoggingInfo
loggingInfo) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe LoggingInfo
a -> UpdateMaintenanceWindowTask
s {$sel:loggingInfo:UpdateMaintenanceWindowTask' :: Maybe LoggingInfo
loggingInfo = Maybe LoggingInfo
a} :: UpdateMaintenanceWindowTask)

-- | The new @MaxConcurrency@ value you want to specify. @MaxConcurrency@ is
-- the number of targets that are allowed to run this task, in parallel.
--
-- Although this element is listed as \"Required: No\", a value can be
-- omitted only when you are registering or updating a
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/maintenance-windows-targetless-tasks.html targetless task>
-- You must provide a value in all other cases.
--
-- For maintenance window tasks without a target specified, you can\'t
-- supply a value for this option. Instead, the system inserts a
-- placeholder value of @1@. This value doesn\'t affect the running of your
-- task.
updateMaintenanceWindowTask_maxConcurrency :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTask_maxConcurrency :: Lens' UpdateMaintenanceWindowTask (Maybe Text)
updateMaintenanceWindowTask_maxConcurrency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe Text
maxConcurrency :: Maybe Text
$sel:maxConcurrency:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
maxConcurrency} -> Maybe Text
maxConcurrency) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe Text
a -> UpdateMaintenanceWindowTask
s {$sel:maxConcurrency:UpdateMaintenanceWindowTask' :: Maybe Text
maxConcurrency = Maybe Text
a} :: UpdateMaintenanceWindowTask)

-- | The new @MaxErrors@ value to specify. @MaxErrors@ is the maximum number
-- of errors that are allowed before the task stops being scheduled.
--
-- Although this element is listed as \"Required: No\", a value can be
-- omitted only when you are registering or updating a
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/maintenance-windows-targetless-tasks.html targetless task>
-- You must provide a value in all other cases.
--
-- For maintenance window tasks without a target specified, you can\'t
-- supply a value for this option. Instead, the system inserts a
-- placeholder value of @1@. This value doesn\'t affect the running of your
-- task.
updateMaintenanceWindowTask_maxErrors :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTask_maxErrors :: Lens' UpdateMaintenanceWindowTask (Maybe Text)
updateMaintenanceWindowTask_maxErrors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe Text
maxErrors :: Maybe Text
$sel:maxErrors:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
maxErrors} -> Maybe Text
maxErrors) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe Text
a -> UpdateMaintenanceWindowTask
s {$sel:maxErrors:UpdateMaintenanceWindowTask' :: Maybe Text
maxErrors = Maybe Text
a} :: UpdateMaintenanceWindowTask)

-- | The new task name to specify.
updateMaintenanceWindowTask_name :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTask_name :: Lens' UpdateMaintenanceWindowTask (Maybe Text)
updateMaintenanceWindowTask_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe Text
name :: Maybe Text
$sel:name:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe Text
a -> UpdateMaintenanceWindowTask
s {$sel:name:UpdateMaintenanceWindowTask' :: Maybe Text
name = Maybe Text
a} :: UpdateMaintenanceWindowTask)

-- | The new task priority to specify. The lower the number, the higher the
-- priority. Tasks that have the same priority are scheduled in parallel.
updateMaintenanceWindowTask_priority :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe Prelude.Natural)
updateMaintenanceWindowTask_priority :: Lens' UpdateMaintenanceWindowTask (Maybe Natural)
updateMaintenanceWindowTask_priority = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe Natural
priority :: Maybe Natural
$sel:priority:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Natural
priority} -> Maybe Natural
priority) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe Natural
a -> UpdateMaintenanceWindowTask
s {$sel:priority:UpdateMaintenanceWindowTask' :: Maybe Natural
priority = Maybe Natural
a} :: UpdateMaintenanceWindowTask)

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

-- | The Amazon Resource Name (ARN) of the IAM service role for Amazon Web
-- Services Systems Manager to assume when running a maintenance window
-- task. If you do not specify a service role ARN, Systems Manager uses
-- your account\'s service-linked role. If no service-linked role for
-- Systems Manager exists in your account, it is created when you run
-- @RegisterTaskWithMaintenanceWindow@.
--
-- For more information, see the following topics in the in the /Amazon Web
-- Services Systems Manager User Guide/:
--
-- -   <https://docs.aws.amazon.com/systems-manager/latest/userguide/using-service-linked-roles.html#slr-permissions Using service-linked roles for Systems Manager>
--
-- -   <https://docs.aws.amazon.com/systems-manager/latest/userguide/sysman-maintenance-permissions.html#maintenance-window-tasks-service-role Should I use a service-linked role or a custom service role to run maintenance window tasks?>
updateMaintenanceWindowTask_serviceRoleArn :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTask_serviceRoleArn :: Lens' UpdateMaintenanceWindowTask (Maybe Text)
updateMaintenanceWindowTask_serviceRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe Text
serviceRoleArn :: Maybe Text
$sel:serviceRoleArn:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
serviceRoleArn} -> Maybe Text
serviceRoleArn) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe Text
a -> UpdateMaintenanceWindowTask
s {$sel:serviceRoleArn:UpdateMaintenanceWindowTask' :: Maybe Text
serviceRoleArn = Maybe Text
a} :: UpdateMaintenanceWindowTask)

-- | The targets (either managed nodes or tags) to modify. Managed nodes are
-- specified using the format
-- @Key=instanceids,Values=instanceID_1,instanceID_2@. Tags are specified
-- using the format @ Key=tag_name,Values=tag_value@.
--
-- One or more targets must be specified for maintenance window Run
-- Command-type tasks. Depending on the task, targets are optional for
-- other maintenance window task types (Automation, Lambda, and Step
-- Functions). For more information about running tasks that don\'t specify
-- targets, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/maintenance-windows-targetless-tasks.html Registering maintenance window tasks without targets>
-- in the /Amazon Web Services Systems Manager User Guide/.
updateMaintenanceWindowTask_targets :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe [Target])
updateMaintenanceWindowTask_targets :: Lens' UpdateMaintenanceWindowTask (Maybe [Target])
updateMaintenanceWindowTask_targets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe [Target]
targets :: Maybe [Target]
$sel:targets:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe [Target]
targets} -> Maybe [Target]
targets) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe [Target]
a -> UpdateMaintenanceWindowTask
s {$sel:targets:UpdateMaintenanceWindowTask' :: Maybe [Target]
targets = Maybe [Target]
a} :: UpdateMaintenanceWindowTask) 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 task ARN to modify.
updateMaintenanceWindowTask_taskArn :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTask_taskArn :: Lens' UpdateMaintenanceWindowTask (Maybe Text)
updateMaintenanceWindowTask_taskArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe Text
taskArn :: Maybe Text
$sel:taskArn:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
taskArn} -> Maybe Text
taskArn) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe Text
a -> UpdateMaintenanceWindowTask
s {$sel:taskArn:UpdateMaintenanceWindowTask' :: Maybe Text
taskArn = Maybe Text
a} :: UpdateMaintenanceWindowTask)

-- | The parameters that the task should use during execution. Populate only
-- the fields that match the task type. All other fields should be empty.
--
-- When you update a maintenance window task that has options specified in
-- @TaskInvocationParameters@, you must provide again all the
-- @TaskInvocationParameters@ values that you want to retain. The values
-- you don\'t specify again are removed. For example, suppose that when you
-- registered a Run Command task, you specified @TaskInvocationParameters@
-- values for @Comment@, @NotificationConfig@, and @OutputS3BucketName@. If
-- you update the maintenance window task and specify only a different
-- @OutputS3BucketName@ value, the values for @Comment@ and
-- @NotificationConfig@ are removed.
updateMaintenanceWindowTask_taskInvocationParameters :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe MaintenanceWindowTaskInvocationParameters)
updateMaintenanceWindowTask_taskInvocationParameters :: Lens'
  UpdateMaintenanceWindowTask
  (Maybe MaintenanceWindowTaskInvocationParameters)
updateMaintenanceWindowTask_taskInvocationParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters :: Maybe MaintenanceWindowTaskInvocationParameters
$sel:taskInvocationParameters:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters} -> Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe MaintenanceWindowTaskInvocationParameters
a -> UpdateMaintenanceWindowTask
s {$sel:taskInvocationParameters:UpdateMaintenanceWindowTask' :: Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters = Maybe MaintenanceWindowTaskInvocationParameters
a} :: UpdateMaintenanceWindowTask)

-- | The parameters to modify.
--
-- @TaskParameters@ has been deprecated. To specify parameters to pass to a
-- task when it runs, instead use the @Parameters@ option in the
-- @TaskInvocationParameters@ structure. For information about how Systems
-- Manager handles these options for the supported maintenance window task
-- types, see MaintenanceWindowTaskInvocationParameters.
--
-- The map has the following format:
--
-- Key: string, between 1 and 255 characters
--
-- Value: an array of strings, each string is between 1 and 255 characters
updateMaintenanceWindowTask_taskParameters :: Lens.Lens' UpdateMaintenanceWindowTask (Prelude.Maybe (Prelude.HashMap Prelude.Text MaintenanceWindowTaskParameterValueExpression))
updateMaintenanceWindowTask_taskParameters :: Lens'
  UpdateMaintenanceWindowTask
  (Maybe
     (HashMap Text MaintenanceWindowTaskParameterValueExpression))
updateMaintenanceWindowTask_taskParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
$sel:taskParameters:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters} -> Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
a -> UpdateMaintenanceWindowTask
s {$sel:taskParameters:UpdateMaintenanceWindowTask' :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters = Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
a} :: UpdateMaintenanceWindowTask) 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | The maintenance window ID that contains the task to modify.
updateMaintenanceWindowTask_windowId :: Lens.Lens' UpdateMaintenanceWindowTask Prelude.Text
updateMaintenanceWindowTask_windowId :: Lens' UpdateMaintenanceWindowTask Text
updateMaintenanceWindowTask_windowId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Text
windowId :: Text
$sel:windowId:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Text
windowId} -> Text
windowId) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Text
a -> UpdateMaintenanceWindowTask
s {$sel:windowId:UpdateMaintenanceWindowTask' :: Text
windowId = Text
a} :: UpdateMaintenanceWindowTask)

-- | The task ID to modify.
updateMaintenanceWindowTask_windowTaskId :: Lens.Lens' UpdateMaintenanceWindowTask Prelude.Text
updateMaintenanceWindowTask_windowTaskId :: Lens' UpdateMaintenanceWindowTask Text
updateMaintenanceWindowTask_windowTaskId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTask' {Text
windowTaskId :: Text
$sel:windowTaskId:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Text
windowTaskId} -> Text
windowTaskId) (\s :: UpdateMaintenanceWindowTask
s@UpdateMaintenanceWindowTask' {} Text
a -> UpdateMaintenanceWindowTask
s {$sel:windowTaskId:UpdateMaintenanceWindowTask' :: Text
windowTaskId = Text
a} :: UpdateMaintenanceWindowTask)

instance Core.AWSRequest UpdateMaintenanceWindowTask where
  type
    AWSResponse UpdateMaintenanceWindowTask =
      UpdateMaintenanceWindowTaskResponse
  request :: (Service -> Service)
-> UpdateMaintenanceWindowTask
-> Request UpdateMaintenanceWindowTask
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 UpdateMaintenanceWindowTask
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateMaintenanceWindowTask)))
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 AlarmConfiguration
-> Maybe MaintenanceWindowTaskCutoffBehavior
-> Maybe (Sensitive Text)
-> Maybe LoggingInfo
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe Text
-> Maybe [Target]
-> Maybe Text
-> Maybe MaintenanceWindowTaskInvocationParameters
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
-> Maybe Text
-> Maybe Text
-> Int
-> UpdateMaintenanceWindowTaskResponse
UpdateMaintenanceWindowTaskResponse'
            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
"AlarmConfiguration")
            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
"CutoffBehavior")
            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
"LoggingInfo")
            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
"MaxConcurrency")
            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
"MaxErrors")
            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
"Priority")
            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
"ServiceRoleArn")
            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
"Targets" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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
"TaskArn")
            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
"TaskInvocationParameters")
            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
"TaskParameters" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"WindowTaskId")
            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 UpdateMaintenanceWindowTask where
  hashWithSalt :: Int -> UpdateMaintenanceWindowTask -> Int
hashWithSalt Int
_salt UpdateMaintenanceWindowTask' {Maybe Bool
Maybe Natural
Maybe [Target]
Maybe Text
Maybe (Sensitive Text)
Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
Maybe AlarmConfiguration
Maybe LoggingInfo
Maybe MaintenanceWindowTaskCutoffBehavior
Maybe MaintenanceWindowTaskInvocationParameters
Text
windowTaskId :: Text
windowId :: Text
taskParameters :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskInvocationParameters :: Maybe MaintenanceWindowTaskInvocationParameters
taskArn :: Maybe Text
targets :: Maybe [Target]
serviceRoleArn :: Maybe Text
replace :: Maybe Bool
priority :: Maybe Natural
name :: Maybe Text
maxErrors :: Maybe Text
maxConcurrency :: Maybe Text
loggingInfo :: Maybe LoggingInfo
description :: Maybe (Sensitive Text)
cutoffBehavior :: Maybe MaintenanceWindowTaskCutoffBehavior
alarmConfiguration :: Maybe AlarmConfiguration
$sel:windowTaskId:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Text
$sel:windowId:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Text
$sel:taskParameters:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
$sel:taskInvocationParameters:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe MaintenanceWindowTaskInvocationParameters
$sel:taskArn:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:targets:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe [Target]
$sel:serviceRoleArn:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:replace:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Bool
$sel:priority:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Natural
$sel:name:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:maxErrors:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:maxConcurrency:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:loggingInfo:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe LoggingInfo
$sel:description:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe (Sensitive Text)
$sel:cutoffBehavior:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe MaintenanceWindowTaskCutoffBehavior
$sel:alarmConfiguration:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe AlarmConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AlarmConfiguration
alarmConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LoggingInfo
loggingInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxConcurrency
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxErrors
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
priority
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
replace
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serviceRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Target]
targets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
taskArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
windowId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
windowTaskId

instance Prelude.NFData UpdateMaintenanceWindowTask where
  rnf :: UpdateMaintenanceWindowTask -> ()
rnf UpdateMaintenanceWindowTask' {Maybe Bool
Maybe Natural
Maybe [Target]
Maybe Text
Maybe (Sensitive Text)
Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
Maybe AlarmConfiguration
Maybe LoggingInfo
Maybe MaintenanceWindowTaskCutoffBehavior
Maybe MaintenanceWindowTaskInvocationParameters
Text
windowTaskId :: Text
windowId :: Text
taskParameters :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskInvocationParameters :: Maybe MaintenanceWindowTaskInvocationParameters
taskArn :: Maybe Text
targets :: Maybe [Target]
serviceRoleArn :: Maybe Text
replace :: Maybe Bool
priority :: Maybe Natural
name :: Maybe Text
maxErrors :: Maybe Text
maxConcurrency :: Maybe Text
loggingInfo :: Maybe LoggingInfo
description :: Maybe (Sensitive Text)
cutoffBehavior :: Maybe MaintenanceWindowTaskCutoffBehavior
alarmConfiguration :: Maybe AlarmConfiguration
$sel:windowTaskId:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Text
$sel:windowId:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Text
$sel:taskParameters:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
$sel:taskInvocationParameters:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe MaintenanceWindowTaskInvocationParameters
$sel:taskArn:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:targets:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe [Target]
$sel:serviceRoleArn:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:replace:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Bool
$sel:priority:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Natural
$sel:name:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:maxErrors:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:maxConcurrency:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:loggingInfo:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe LoggingInfo
$sel:description:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe (Sensitive Text)
$sel:cutoffBehavior:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe MaintenanceWindowTaskCutoffBehavior
$sel:alarmConfiguration:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe AlarmConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AlarmConfiguration
alarmConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior
      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 LoggingInfo
loggingInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxConcurrency
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxErrors
      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 Natural
priority
      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
serviceRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Target]
targets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
taskArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
windowId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
windowTaskId

instance Data.ToHeaders UpdateMaintenanceWindowTask where
  toHeaders :: UpdateMaintenanceWindowTask -> 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.UpdateMaintenanceWindowTask" ::
                          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 UpdateMaintenanceWindowTask where
  toJSON :: UpdateMaintenanceWindowTask -> Value
toJSON UpdateMaintenanceWindowTask' {Maybe Bool
Maybe Natural
Maybe [Target]
Maybe Text
Maybe (Sensitive Text)
Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
Maybe AlarmConfiguration
Maybe LoggingInfo
Maybe MaintenanceWindowTaskCutoffBehavior
Maybe MaintenanceWindowTaskInvocationParameters
Text
windowTaskId :: Text
windowId :: Text
taskParameters :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskInvocationParameters :: Maybe MaintenanceWindowTaskInvocationParameters
taskArn :: Maybe Text
targets :: Maybe [Target]
serviceRoleArn :: Maybe Text
replace :: Maybe Bool
priority :: Maybe Natural
name :: Maybe Text
maxErrors :: Maybe Text
maxConcurrency :: Maybe Text
loggingInfo :: Maybe LoggingInfo
description :: Maybe (Sensitive Text)
cutoffBehavior :: Maybe MaintenanceWindowTaskCutoffBehavior
alarmConfiguration :: Maybe AlarmConfiguration
$sel:windowTaskId:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Text
$sel:windowId:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Text
$sel:taskParameters:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
$sel:taskInvocationParameters:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe MaintenanceWindowTaskInvocationParameters
$sel:taskArn:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:targets:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe [Target]
$sel:serviceRoleArn:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:replace:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Bool
$sel:priority:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Natural
$sel:name:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:maxErrors:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:maxConcurrency:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe Text
$sel:loggingInfo:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe LoggingInfo
$sel:description:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe (Sensitive Text)
$sel:cutoffBehavior:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask
-> Maybe MaintenanceWindowTaskCutoffBehavior
$sel:alarmConfiguration:UpdateMaintenanceWindowTask' :: UpdateMaintenanceWindowTask -> Maybe AlarmConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AlarmConfiguration" 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 AlarmConfiguration
alarmConfiguration,
            (Key
"CutoffBehavior" 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 MaintenanceWindowTaskCutoffBehavior
cutoffBehavior,
            (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
"LoggingInfo" 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 LoggingInfo
loggingInfo,
            (Key
"MaxConcurrency" 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
maxConcurrency,
            (Key
"MaxErrors" 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
maxErrors,
            (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
"Priority" 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
priority,
            (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
"ServiceRoleArn" 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
serviceRoleArn,
            (Key
"Targets" 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 [Target]
targets,
            (Key
"TaskArn" 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
taskArn,
            (Key
"TaskInvocationParameters" 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 MaintenanceWindowTaskInvocationParameters
taskInvocationParameters,
            (Key
"TaskParameters" 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
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters,
            forall a. a -> Maybe a
Prelude.Just (Key
"WindowId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
windowId),
            forall a. a -> Maybe a
Prelude.Just (Key
"WindowTaskId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
windowTaskId)
          ]
      )

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

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

-- | /See:/ 'newUpdateMaintenanceWindowTaskResponse' smart constructor.
data UpdateMaintenanceWindowTaskResponse = UpdateMaintenanceWindowTaskResponse'
  { -- | The details for the CloudWatch alarm you applied to your maintenance
    -- window task.
    UpdateMaintenanceWindowTaskResponse -> Maybe AlarmConfiguration
alarmConfiguration :: Prelude.Maybe AlarmConfiguration,
    -- | The specification for whether tasks should continue to run after the
    -- cutoff time specified in the maintenance windows is reached.
    UpdateMaintenanceWindowTaskResponse
-> Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior :: Prelude.Maybe MaintenanceWindowTaskCutoffBehavior,
    -- | The updated task description.
    UpdateMaintenanceWindowTaskResponse -> Maybe (Sensitive Text)
description :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The updated logging information in Amazon S3.
    --
    -- @LoggingInfo@ has been deprecated. To specify an Amazon Simple Storage
    -- Service (Amazon S3) bucket to contain logs, instead use the
    -- @OutputS3BucketName@ and @OutputS3KeyPrefix@ options in the
    -- @TaskInvocationParameters@ structure. For information about how Amazon
    -- Web Services Systems Manager handles these options for the supported
    -- maintenance window task types, see
    -- MaintenanceWindowTaskInvocationParameters.
    UpdateMaintenanceWindowTaskResponse -> Maybe LoggingInfo
loggingInfo :: Prelude.Maybe LoggingInfo,
    -- | The updated @MaxConcurrency@ value.
    UpdateMaintenanceWindowTaskResponse -> Maybe Text
maxConcurrency :: Prelude.Maybe Prelude.Text,
    -- | The updated @MaxErrors@ value.
    UpdateMaintenanceWindowTaskResponse -> Maybe Text
maxErrors :: Prelude.Maybe Prelude.Text,
    -- | The updated task name.
    UpdateMaintenanceWindowTaskResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The updated priority value.
    UpdateMaintenanceWindowTaskResponse -> Maybe Natural
priority :: Prelude.Maybe Prelude.Natural,
    -- | The Amazon Resource Name (ARN) of the Identity and Access Management
    -- (IAM) service role to use to publish Amazon Simple Notification Service
    -- (Amazon SNS) notifications for maintenance window Run Command tasks.
    UpdateMaintenanceWindowTaskResponse -> Maybe Text
serviceRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The updated target values.
    UpdateMaintenanceWindowTaskResponse -> Maybe [Target]
targets :: Prelude.Maybe [Target],
    -- | The updated task ARN value.
    UpdateMaintenanceWindowTaskResponse -> Maybe Text
taskArn :: Prelude.Maybe Prelude.Text,
    -- | The updated parameter values.
    UpdateMaintenanceWindowTaskResponse
-> Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters :: Prelude.Maybe MaintenanceWindowTaskInvocationParameters,
    -- | The updated parameter values.
    --
    -- @TaskParameters@ has been deprecated. To specify parameters to pass to a
    -- task when it runs, instead use the @Parameters@ option in the
    -- @TaskInvocationParameters@ structure. For information about how Systems
    -- Manager handles these options for the supported maintenance window task
    -- types, see MaintenanceWindowTaskInvocationParameters.
    UpdateMaintenanceWindowTaskResponse
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text (Data.Sensitive MaintenanceWindowTaskParameterValueExpression))),
    -- | The ID of the maintenance window that was updated.
    UpdateMaintenanceWindowTaskResponse -> Maybe Text
windowId :: Prelude.Maybe Prelude.Text,
    -- | The task ID of the maintenance window that was updated.
    UpdateMaintenanceWindowTaskResponse -> Maybe Text
windowTaskId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateMaintenanceWindowTaskResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateMaintenanceWindowTaskResponse
-> UpdateMaintenanceWindowTaskResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateMaintenanceWindowTaskResponse
-> UpdateMaintenanceWindowTaskResponse -> Bool
$c/= :: UpdateMaintenanceWindowTaskResponse
-> UpdateMaintenanceWindowTaskResponse -> Bool
== :: UpdateMaintenanceWindowTaskResponse
-> UpdateMaintenanceWindowTaskResponse -> Bool
$c== :: UpdateMaintenanceWindowTaskResponse
-> UpdateMaintenanceWindowTaskResponse -> Bool
Prelude.Eq, Int -> UpdateMaintenanceWindowTaskResponse -> ShowS
[UpdateMaintenanceWindowTaskResponse] -> ShowS
UpdateMaintenanceWindowTaskResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateMaintenanceWindowTaskResponse] -> ShowS
$cshowList :: [UpdateMaintenanceWindowTaskResponse] -> ShowS
show :: UpdateMaintenanceWindowTaskResponse -> String
$cshow :: UpdateMaintenanceWindowTaskResponse -> String
showsPrec :: Int -> UpdateMaintenanceWindowTaskResponse -> ShowS
$cshowsPrec :: Int -> UpdateMaintenanceWindowTaskResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateMaintenanceWindowTaskResponse x
-> UpdateMaintenanceWindowTaskResponse
forall x.
UpdateMaintenanceWindowTaskResponse
-> Rep UpdateMaintenanceWindowTaskResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateMaintenanceWindowTaskResponse x
-> UpdateMaintenanceWindowTaskResponse
$cfrom :: forall x.
UpdateMaintenanceWindowTaskResponse
-> Rep UpdateMaintenanceWindowTaskResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateMaintenanceWindowTaskResponse' 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:
--
-- 'alarmConfiguration', 'updateMaintenanceWindowTaskResponse_alarmConfiguration' - The details for the CloudWatch alarm you applied to your maintenance
-- window task.
--
-- 'cutoffBehavior', 'updateMaintenanceWindowTaskResponse_cutoffBehavior' - The specification for whether tasks should continue to run after the
-- cutoff time specified in the maintenance windows is reached.
--
-- 'description', 'updateMaintenanceWindowTaskResponse_description' - The updated task description.
--
-- 'loggingInfo', 'updateMaintenanceWindowTaskResponse_loggingInfo' - The updated logging information in Amazon S3.
--
-- @LoggingInfo@ has been deprecated. To specify an Amazon Simple Storage
-- Service (Amazon S3) bucket to contain logs, instead use the
-- @OutputS3BucketName@ and @OutputS3KeyPrefix@ options in the
-- @TaskInvocationParameters@ structure. For information about how Amazon
-- Web Services Systems Manager handles these options for the supported
-- maintenance window task types, see
-- MaintenanceWindowTaskInvocationParameters.
--
-- 'maxConcurrency', 'updateMaintenanceWindowTaskResponse_maxConcurrency' - The updated @MaxConcurrency@ value.
--
-- 'maxErrors', 'updateMaintenanceWindowTaskResponse_maxErrors' - The updated @MaxErrors@ value.
--
-- 'name', 'updateMaintenanceWindowTaskResponse_name' - The updated task name.
--
-- 'priority', 'updateMaintenanceWindowTaskResponse_priority' - The updated priority value.
--
-- 'serviceRoleArn', 'updateMaintenanceWindowTaskResponse_serviceRoleArn' - The Amazon Resource Name (ARN) of the Identity and Access Management
-- (IAM) service role to use to publish Amazon Simple Notification Service
-- (Amazon SNS) notifications for maintenance window Run Command tasks.
--
-- 'targets', 'updateMaintenanceWindowTaskResponse_targets' - The updated target values.
--
-- 'taskArn', 'updateMaintenanceWindowTaskResponse_taskArn' - The updated task ARN value.
--
-- 'taskInvocationParameters', 'updateMaintenanceWindowTaskResponse_taskInvocationParameters' - The updated parameter values.
--
-- 'taskParameters', 'updateMaintenanceWindowTaskResponse_taskParameters' - The updated parameter values.
--
-- @TaskParameters@ has been deprecated. To specify parameters to pass to a
-- task when it runs, instead use the @Parameters@ option in the
-- @TaskInvocationParameters@ structure. For information about how Systems
-- Manager handles these options for the supported maintenance window task
-- types, see MaintenanceWindowTaskInvocationParameters.
--
-- 'windowId', 'updateMaintenanceWindowTaskResponse_windowId' - The ID of the maintenance window that was updated.
--
-- 'windowTaskId', 'updateMaintenanceWindowTaskResponse_windowTaskId' - The task ID of the maintenance window that was updated.
--
-- 'httpStatus', 'updateMaintenanceWindowTaskResponse_httpStatus' - The response's http status code.
newUpdateMaintenanceWindowTaskResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateMaintenanceWindowTaskResponse
newUpdateMaintenanceWindowTaskResponse :: Int -> UpdateMaintenanceWindowTaskResponse
newUpdateMaintenanceWindowTaskResponse Int
pHttpStatus_ =
  UpdateMaintenanceWindowTaskResponse'
    { $sel:alarmConfiguration:UpdateMaintenanceWindowTaskResponse' :: Maybe AlarmConfiguration
alarmConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:cutoffBehavior:UpdateMaintenanceWindowTaskResponse' :: Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior = forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateMaintenanceWindowTaskResponse' :: Maybe (Sensitive Text)
description = forall a. Maybe a
Prelude.Nothing,
      $sel:loggingInfo:UpdateMaintenanceWindowTaskResponse' :: Maybe LoggingInfo
loggingInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:maxConcurrency:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
maxConcurrency = forall a. Maybe a
Prelude.Nothing,
      $sel:maxErrors:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
maxErrors = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:priority:UpdateMaintenanceWindowTaskResponse' :: Maybe Natural
priority = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceRoleArn:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
serviceRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:targets:UpdateMaintenanceWindowTaskResponse' :: Maybe [Target]
targets = forall a. Maybe a
Prelude.Nothing,
      $sel:taskArn:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
taskArn = forall a. Maybe a
Prelude.Nothing,
      $sel:taskInvocationParameters:UpdateMaintenanceWindowTaskResponse' :: Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters =
        forall a. Maybe a
Prelude.Nothing,
      $sel:taskParameters:UpdateMaintenanceWindowTaskResponse' :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:windowId:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
windowId = forall a. Maybe a
Prelude.Nothing,
      $sel:windowTaskId:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
windowTaskId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateMaintenanceWindowTaskResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The details for the CloudWatch alarm you applied to your maintenance
-- window task.
updateMaintenanceWindowTaskResponse_alarmConfiguration :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe AlarmConfiguration)
updateMaintenanceWindowTaskResponse_alarmConfiguration :: Lens'
  UpdateMaintenanceWindowTaskResponse (Maybe AlarmConfiguration)
updateMaintenanceWindowTaskResponse_alarmConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe AlarmConfiguration
alarmConfiguration :: Maybe AlarmConfiguration
$sel:alarmConfiguration:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe AlarmConfiguration
alarmConfiguration} -> Maybe AlarmConfiguration
alarmConfiguration) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe AlarmConfiguration
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:alarmConfiguration:UpdateMaintenanceWindowTaskResponse' :: Maybe AlarmConfiguration
alarmConfiguration = Maybe AlarmConfiguration
a} :: UpdateMaintenanceWindowTaskResponse)

-- | The specification for whether tasks should continue to run after the
-- cutoff time specified in the maintenance windows is reached.
updateMaintenanceWindowTaskResponse_cutoffBehavior :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe MaintenanceWindowTaskCutoffBehavior)
updateMaintenanceWindowTaskResponse_cutoffBehavior :: Lens'
  UpdateMaintenanceWindowTaskResponse
  (Maybe MaintenanceWindowTaskCutoffBehavior)
updateMaintenanceWindowTaskResponse_cutoffBehavior = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior :: Maybe MaintenanceWindowTaskCutoffBehavior
$sel:cutoffBehavior:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse
-> Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior} -> Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe MaintenanceWindowTaskCutoffBehavior
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:cutoffBehavior:UpdateMaintenanceWindowTaskResponse' :: Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior = Maybe MaintenanceWindowTaskCutoffBehavior
a} :: UpdateMaintenanceWindowTaskResponse)

-- | The updated task description.
updateMaintenanceWindowTaskResponse_description :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTaskResponse_description :: Lens' UpdateMaintenanceWindowTaskResponse (Maybe Text)
updateMaintenanceWindowTaskResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:description:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe (Sensitive Text)
description} -> Maybe (Sensitive Text)
description) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe (Sensitive Text)
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:description:UpdateMaintenanceWindowTaskResponse' :: Maybe (Sensitive Text)
description = Maybe (Sensitive Text)
a} :: UpdateMaintenanceWindowTaskResponse) 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 updated logging information in Amazon S3.
--
-- @LoggingInfo@ has been deprecated. To specify an Amazon Simple Storage
-- Service (Amazon S3) bucket to contain logs, instead use the
-- @OutputS3BucketName@ and @OutputS3KeyPrefix@ options in the
-- @TaskInvocationParameters@ structure. For information about how Amazon
-- Web Services Systems Manager handles these options for the supported
-- maintenance window task types, see
-- MaintenanceWindowTaskInvocationParameters.
updateMaintenanceWindowTaskResponse_loggingInfo :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe LoggingInfo)
updateMaintenanceWindowTaskResponse_loggingInfo :: Lens' UpdateMaintenanceWindowTaskResponse (Maybe LoggingInfo)
updateMaintenanceWindowTaskResponse_loggingInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe LoggingInfo
loggingInfo :: Maybe LoggingInfo
$sel:loggingInfo:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe LoggingInfo
loggingInfo} -> Maybe LoggingInfo
loggingInfo) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe LoggingInfo
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:loggingInfo:UpdateMaintenanceWindowTaskResponse' :: Maybe LoggingInfo
loggingInfo = Maybe LoggingInfo
a} :: UpdateMaintenanceWindowTaskResponse)

-- | The updated @MaxConcurrency@ value.
updateMaintenanceWindowTaskResponse_maxConcurrency :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTaskResponse_maxConcurrency :: Lens' UpdateMaintenanceWindowTaskResponse (Maybe Text)
updateMaintenanceWindowTaskResponse_maxConcurrency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe Text
maxConcurrency :: Maybe Text
$sel:maxConcurrency:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
maxConcurrency} -> Maybe Text
maxConcurrency) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe Text
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:maxConcurrency:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
maxConcurrency = Maybe Text
a} :: UpdateMaintenanceWindowTaskResponse)

-- | The updated @MaxErrors@ value.
updateMaintenanceWindowTaskResponse_maxErrors :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTaskResponse_maxErrors :: Lens' UpdateMaintenanceWindowTaskResponse (Maybe Text)
updateMaintenanceWindowTaskResponse_maxErrors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe Text
maxErrors :: Maybe Text
$sel:maxErrors:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
maxErrors} -> Maybe Text
maxErrors) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe Text
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:maxErrors:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
maxErrors = Maybe Text
a} :: UpdateMaintenanceWindowTaskResponse)

-- | The updated task name.
updateMaintenanceWindowTaskResponse_name :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTaskResponse_name :: Lens' UpdateMaintenanceWindowTaskResponse (Maybe Text)
updateMaintenanceWindowTaskResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe Text
name :: Maybe Text
$sel:name:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe Text
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:name:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
name = Maybe Text
a} :: UpdateMaintenanceWindowTaskResponse)

-- | The updated priority value.
updateMaintenanceWindowTaskResponse_priority :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe Prelude.Natural)
updateMaintenanceWindowTaskResponse_priority :: Lens' UpdateMaintenanceWindowTaskResponse (Maybe Natural)
updateMaintenanceWindowTaskResponse_priority = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe Natural
priority :: Maybe Natural
$sel:priority:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Natural
priority} -> Maybe Natural
priority) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe Natural
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:priority:UpdateMaintenanceWindowTaskResponse' :: Maybe Natural
priority = Maybe Natural
a} :: UpdateMaintenanceWindowTaskResponse)

-- | The Amazon Resource Name (ARN) of the Identity and Access Management
-- (IAM) service role to use to publish Amazon Simple Notification Service
-- (Amazon SNS) notifications for maintenance window Run Command tasks.
updateMaintenanceWindowTaskResponse_serviceRoleArn :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTaskResponse_serviceRoleArn :: Lens' UpdateMaintenanceWindowTaskResponse (Maybe Text)
updateMaintenanceWindowTaskResponse_serviceRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe Text
serviceRoleArn :: Maybe Text
$sel:serviceRoleArn:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
serviceRoleArn} -> Maybe Text
serviceRoleArn) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe Text
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:serviceRoleArn:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
serviceRoleArn = Maybe Text
a} :: UpdateMaintenanceWindowTaskResponse)

-- | The updated target values.
updateMaintenanceWindowTaskResponse_targets :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe [Target])
updateMaintenanceWindowTaskResponse_targets :: Lens' UpdateMaintenanceWindowTaskResponse (Maybe [Target])
updateMaintenanceWindowTaskResponse_targets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe [Target]
targets :: Maybe [Target]
$sel:targets:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe [Target]
targets} -> Maybe [Target]
targets) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe [Target]
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:targets:UpdateMaintenanceWindowTaskResponse' :: Maybe [Target]
targets = Maybe [Target]
a} :: UpdateMaintenanceWindowTaskResponse) 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 updated task ARN value.
updateMaintenanceWindowTaskResponse_taskArn :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTaskResponse_taskArn :: Lens' UpdateMaintenanceWindowTaskResponse (Maybe Text)
updateMaintenanceWindowTaskResponse_taskArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe Text
taskArn :: Maybe Text
$sel:taskArn:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
taskArn} -> Maybe Text
taskArn) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe Text
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:taskArn:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
taskArn = Maybe Text
a} :: UpdateMaintenanceWindowTaskResponse)

-- | The updated parameter values.
updateMaintenanceWindowTaskResponse_taskInvocationParameters :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe MaintenanceWindowTaskInvocationParameters)
updateMaintenanceWindowTaskResponse_taskInvocationParameters :: Lens'
  UpdateMaintenanceWindowTaskResponse
  (Maybe MaintenanceWindowTaskInvocationParameters)
updateMaintenanceWindowTaskResponse_taskInvocationParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters :: Maybe MaintenanceWindowTaskInvocationParameters
$sel:taskInvocationParameters:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse
-> Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters} -> Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe MaintenanceWindowTaskInvocationParameters
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:taskInvocationParameters:UpdateMaintenanceWindowTaskResponse' :: Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters = Maybe MaintenanceWindowTaskInvocationParameters
a} :: UpdateMaintenanceWindowTaskResponse)

-- | The updated parameter values.
--
-- @TaskParameters@ has been deprecated. To specify parameters to pass to a
-- task when it runs, instead use the @Parameters@ option in the
-- @TaskInvocationParameters@ structure. For information about how Systems
-- Manager handles these options for the supported maintenance window task
-- types, see MaintenanceWindowTaskInvocationParameters.
updateMaintenanceWindowTaskResponse_taskParameters :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text MaintenanceWindowTaskParameterValueExpression))
updateMaintenanceWindowTaskResponse_taskParameters :: Lens'
  UpdateMaintenanceWindowTaskResponse
  (Maybe
     (HashMap Text MaintenanceWindowTaskParameterValueExpression))
updateMaintenanceWindowTaskResponse_taskParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
$sel:taskParameters:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters} -> Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:taskParameters:UpdateMaintenanceWindowTaskResponse' :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters = Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
a} :: UpdateMaintenanceWindowTaskResponse) 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

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

-- | The task ID of the maintenance window that was updated.
updateMaintenanceWindowTaskResponse_windowTaskId :: Lens.Lens' UpdateMaintenanceWindowTaskResponse (Prelude.Maybe Prelude.Text)
updateMaintenanceWindowTaskResponse_windowTaskId :: Lens' UpdateMaintenanceWindowTaskResponse (Maybe Text)
updateMaintenanceWindowTaskResponse_windowTaskId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMaintenanceWindowTaskResponse' {Maybe Text
windowTaskId :: Maybe Text
$sel:windowTaskId:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
windowTaskId} -> Maybe Text
windowTaskId) (\s :: UpdateMaintenanceWindowTaskResponse
s@UpdateMaintenanceWindowTaskResponse' {} Maybe Text
a -> UpdateMaintenanceWindowTaskResponse
s {$sel:windowTaskId:UpdateMaintenanceWindowTaskResponse' :: Maybe Text
windowTaskId = Maybe Text
a} :: UpdateMaintenanceWindowTaskResponse)

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

instance
  Prelude.NFData
    UpdateMaintenanceWindowTaskResponse
  where
  rnf :: UpdateMaintenanceWindowTaskResponse -> ()
rnf UpdateMaintenanceWindowTaskResponse' {Int
Maybe Natural
Maybe [Target]
Maybe Text
Maybe (Sensitive Text)
Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
Maybe AlarmConfiguration
Maybe LoggingInfo
Maybe MaintenanceWindowTaskCutoffBehavior
Maybe MaintenanceWindowTaskInvocationParameters
httpStatus :: Int
windowTaskId :: Maybe Text
windowId :: Maybe Text
taskParameters :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskInvocationParameters :: Maybe MaintenanceWindowTaskInvocationParameters
taskArn :: Maybe Text
targets :: Maybe [Target]
serviceRoleArn :: Maybe Text
priority :: Maybe Natural
name :: Maybe Text
maxErrors :: Maybe Text
maxConcurrency :: Maybe Text
loggingInfo :: Maybe LoggingInfo
description :: Maybe (Sensitive Text)
cutoffBehavior :: Maybe MaintenanceWindowTaskCutoffBehavior
alarmConfiguration :: Maybe AlarmConfiguration
$sel:httpStatus:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Int
$sel:windowTaskId:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
$sel:windowId:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
$sel:taskParameters:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
$sel:taskInvocationParameters:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse
-> Maybe MaintenanceWindowTaskInvocationParameters
$sel:taskArn:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
$sel:targets:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe [Target]
$sel:serviceRoleArn:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
$sel:priority:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Natural
$sel:name:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
$sel:maxErrors:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
$sel:maxConcurrency:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe Text
$sel:loggingInfo:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe LoggingInfo
$sel:description:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe (Sensitive Text)
$sel:cutoffBehavior:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse
-> Maybe MaintenanceWindowTaskCutoffBehavior
$sel:alarmConfiguration:UpdateMaintenanceWindowTaskResponse' :: UpdateMaintenanceWindowTaskResponse -> Maybe AlarmConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AlarmConfiguration
alarmConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior
      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 LoggingInfo
loggingInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxConcurrency
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxErrors
      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 Natural
priority
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serviceRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Target]
targets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
taskArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MaintenanceWindowTaskInvocationParameters
taskInvocationParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters
      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 Maybe Text
windowTaskId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus