{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.SSM.Types.MaintenanceWindowTask
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.SSM.Types.MaintenanceWindowTask where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.SSM.Types.AlarmConfiguration
import Amazonka.SSM.Types.LoggingInfo
import Amazonka.SSM.Types.MaintenanceWindowTaskCutoffBehavior
import Amazonka.SSM.Types.MaintenanceWindowTaskParameterValueExpression
import Amazonka.SSM.Types.MaintenanceWindowTaskType
import Amazonka.SSM.Types.Target

-- | Information about a task defined for a maintenance window.
--
-- /See:/ 'newMaintenanceWindowTask' smart constructor.
data MaintenanceWindowTask = MaintenanceWindowTask'
  { -- | The details for the CloudWatch alarm applied to your maintenance window
    -- task.
    MaintenanceWindowTask -> 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.
    MaintenanceWindowTask -> Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior :: Prelude.Maybe MaintenanceWindowTaskCutoffBehavior,
    -- | A description of the task.
    MaintenanceWindowTask -> Maybe (Sensitive Text)
description :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | Information about an S3 bucket to write task-level logs to.
    --
    -- @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.
    MaintenanceWindowTask -> Maybe LoggingInfo
loggingInfo :: Prelude.Maybe LoggingInfo,
    -- | The maximum number of targets this task can be run for, 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.
    MaintenanceWindowTask -> Maybe Text
maxConcurrency :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of errors allowed before this 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.
    MaintenanceWindowTask -> Maybe Text
maxErrors :: Prelude.Maybe Prelude.Text,
    -- | The task name.
    MaintenanceWindowTask -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The priority of the task in the maintenance window. The lower the
    -- number, the higher the priority. Tasks that have the same priority are
    -- scheduled in parallel.
    MaintenanceWindowTask -> 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.
    MaintenanceWindowTask -> Maybe Text
serviceRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The targets (either managed nodes or tags). Managed nodes are specified
    -- using @Key=instanceids,Values=\<instanceid1>,\<instanceid2>@. Tags are
    -- specified using @Key=\<tag name>,Values=\<tag value>@.
    MaintenanceWindowTask -> Maybe [Target]
targets :: Prelude.Maybe [Target],
    -- | The resource that the task uses during execution. For @RUN_COMMAND@ and
    -- @AUTOMATION@ task types, @TaskArn@ is the Amazon Web Services Systems
    -- Manager (SSM document) name or ARN. For @LAMBDA@ tasks, it\'s the
    -- function name or ARN. For @STEP_FUNCTIONS@ tasks, it\'s the state
    -- machine ARN.
    MaintenanceWindowTask -> Maybe Text
taskArn :: Prelude.Maybe Prelude.Text,
    -- | The parameters that should be passed to the task when it is run.
    --
    -- @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.
    MaintenanceWindowTask
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text (Data.Sensitive MaintenanceWindowTaskParameterValueExpression))),
    -- | The type of task.
    MaintenanceWindowTask -> Maybe MaintenanceWindowTaskType
type' :: Prelude.Maybe MaintenanceWindowTaskType,
    -- | The ID of the maintenance window where the task is registered.
    MaintenanceWindowTask -> Maybe Text
windowId :: Prelude.Maybe Prelude.Text,
    -- | The task ID.
    MaintenanceWindowTask -> Maybe Text
windowTaskId :: Prelude.Maybe Prelude.Text
  }
  deriving (MaintenanceWindowTask -> MaintenanceWindowTask -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MaintenanceWindowTask -> MaintenanceWindowTask -> Bool
$c/= :: MaintenanceWindowTask -> MaintenanceWindowTask -> Bool
== :: MaintenanceWindowTask -> MaintenanceWindowTask -> Bool
$c== :: MaintenanceWindowTask -> MaintenanceWindowTask -> Bool
Prelude.Eq, Int -> MaintenanceWindowTask -> ShowS
[MaintenanceWindowTask] -> ShowS
MaintenanceWindowTask -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MaintenanceWindowTask] -> ShowS
$cshowList :: [MaintenanceWindowTask] -> ShowS
show :: MaintenanceWindowTask -> String
$cshow :: MaintenanceWindowTask -> String
showsPrec :: Int -> MaintenanceWindowTask -> ShowS
$cshowsPrec :: Int -> MaintenanceWindowTask -> ShowS
Prelude.Show, forall x. Rep MaintenanceWindowTask x -> MaintenanceWindowTask
forall x. MaintenanceWindowTask -> Rep MaintenanceWindowTask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MaintenanceWindowTask x -> MaintenanceWindowTask
$cfrom :: forall x. MaintenanceWindowTask -> Rep MaintenanceWindowTask x
Prelude.Generic)

-- |
-- Create a value of 'MaintenanceWindowTask' 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', 'maintenanceWindowTask_alarmConfiguration' - The details for the CloudWatch alarm applied to your maintenance window
-- task.
--
-- 'cutoffBehavior', 'maintenanceWindowTask_cutoffBehavior' - The specification for whether tasks should continue to run after the
-- cutoff time specified in the maintenance windows is reached.
--
-- 'description', 'maintenanceWindowTask_description' - A description of the task.
--
-- 'loggingInfo', 'maintenanceWindowTask_loggingInfo' - Information about an S3 bucket to write task-level logs to.
--
-- @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', 'maintenanceWindowTask_maxConcurrency' - The maximum number of targets this task can be run for, 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', 'maintenanceWindowTask_maxErrors' - The maximum number of errors allowed before this 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', 'maintenanceWindowTask_name' - The task name.
--
-- 'priority', 'maintenanceWindowTask_priority' - The priority of the task in the maintenance window. The lower the
-- number, the higher the priority. Tasks that have the same priority are
-- scheduled in parallel.
--
-- 'serviceRoleArn', 'maintenanceWindowTask_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', 'maintenanceWindowTask_targets' - The targets (either managed nodes or tags). Managed nodes are specified
-- using @Key=instanceids,Values=\<instanceid1>,\<instanceid2>@. Tags are
-- specified using @Key=\<tag name>,Values=\<tag value>@.
--
-- 'taskArn', 'maintenanceWindowTask_taskArn' - The resource that the task uses during execution. For @RUN_COMMAND@ and
-- @AUTOMATION@ task types, @TaskArn@ is the Amazon Web Services Systems
-- Manager (SSM document) name or ARN. For @LAMBDA@ tasks, it\'s the
-- function name or ARN. For @STEP_FUNCTIONS@ tasks, it\'s the state
-- machine ARN.
--
-- 'taskParameters', 'maintenanceWindowTask_taskParameters' - The parameters that should be passed to the task when it is run.
--
-- @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.
--
-- 'type'', 'maintenanceWindowTask_type' - The type of task.
--
-- 'windowId', 'maintenanceWindowTask_windowId' - The ID of the maintenance window where the task is registered.
--
-- 'windowTaskId', 'maintenanceWindowTask_windowTaskId' - The task ID.
newMaintenanceWindowTask ::
  MaintenanceWindowTask
newMaintenanceWindowTask :: MaintenanceWindowTask
newMaintenanceWindowTask =
  MaintenanceWindowTask'
    { $sel:alarmConfiguration:MaintenanceWindowTask' :: Maybe AlarmConfiguration
alarmConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:cutoffBehavior:MaintenanceWindowTask' :: Maybe MaintenanceWindowTaskCutoffBehavior
cutoffBehavior = forall a. Maybe a
Prelude.Nothing,
      $sel:description:MaintenanceWindowTask' :: Maybe (Sensitive Text)
description = forall a. Maybe a
Prelude.Nothing,
      $sel:loggingInfo:MaintenanceWindowTask' :: Maybe LoggingInfo
loggingInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:maxConcurrency:MaintenanceWindowTask' :: Maybe Text
maxConcurrency = forall a. Maybe a
Prelude.Nothing,
      $sel:maxErrors:MaintenanceWindowTask' :: Maybe Text
maxErrors = forall a. Maybe a
Prelude.Nothing,
      $sel:name:MaintenanceWindowTask' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:priority:MaintenanceWindowTask' :: Maybe Natural
priority = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceRoleArn:MaintenanceWindowTask' :: Maybe Text
serviceRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:targets:MaintenanceWindowTask' :: Maybe [Target]
targets = forall a. Maybe a
Prelude.Nothing,
      $sel:taskArn:MaintenanceWindowTask' :: Maybe Text
taskArn = forall a. Maybe a
Prelude.Nothing,
      $sel:taskParameters:MaintenanceWindowTask' :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:type':MaintenanceWindowTask' :: Maybe MaintenanceWindowTaskType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:windowId:MaintenanceWindowTask' :: Maybe Text
windowId = forall a. Maybe a
Prelude.Nothing,
      $sel:windowTaskId:MaintenanceWindowTask' :: Maybe Text
windowTaskId = forall a. Maybe a
Prelude.Nothing
    }

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

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

-- | A description of the task.
maintenanceWindowTask_description :: Lens.Lens' MaintenanceWindowTask (Prelude.Maybe Prelude.Text)
maintenanceWindowTask_description :: Lens' MaintenanceWindowTask (Maybe Text)
maintenanceWindowTask_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowTask' {Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:description:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe (Sensitive Text)
description} -> Maybe (Sensitive Text)
description) (\s :: MaintenanceWindowTask
s@MaintenanceWindowTask' {} Maybe (Sensitive Text)
a -> MaintenanceWindowTask
s {$sel:description:MaintenanceWindowTask' :: Maybe (Sensitive Text)
description = Maybe (Sensitive Text)
a} :: MaintenanceWindowTask) 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

-- | Information about an S3 bucket to write task-level logs to.
--
-- @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.
maintenanceWindowTask_loggingInfo :: Lens.Lens' MaintenanceWindowTask (Prelude.Maybe LoggingInfo)
maintenanceWindowTask_loggingInfo :: Lens' MaintenanceWindowTask (Maybe LoggingInfo)
maintenanceWindowTask_loggingInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowTask' {Maybe LoggingInfo
loggingInfo :: Maybe LoggingInfo
$sel:loggingInfo:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe LoggingInfo
loggingInfo} -> Maybe LoggingInfo
loggingInfo) (\s :: MaintenanceWindowTask
s@MaintenanceWindowTask' {} Maybe LoggingInfo
a -> MaintenanceWindowTask
s {$sel:loggingInfo:MaintenanceWindowTask' :: Maybe LoggingInfo
loggingInfo = Maybe LoggingInfo
a} :: MaintenanceWindowTask)

-- | The maximum number of targets this task can be run for, 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.
maintenanceWindowTask_maxConcurrency :: Lens.Lens' MaintenanceWindowTask (Prelude.Maybe Prelude.Text)
maintenanceWindowTask_maxConcurrency :: Lens' MaintenanceWindowTask (Maybe Text)
maintenanceWindowTask_maxConcurrency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowTask' {Maybe Text
maxConcurrency :: Maybe Text
$sel:maxConcurrency:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
maxConcurrency} -> Maybe Text
maxConcurrency) (\s :: MaintenanceWindowTask
s@MaintenanceWindowTask' {} Maybe Text
a -> MaintenanceWindowTask
s {$sel:maxConcurrency:MaintenanceWindowTask' :: Maybe Text
maxConcurrency = Maybe Text
a} :: MaintenanceWindowTask)

-- | The maximum number of errors allowed before this 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.
maintenanceWindowTask_maxErrors :: Lens.Lens' MaintenanceWindowTask (Prelude.Maybe Prelude.Text)
maintenanceWindowTask_maxErrors :: Lens' MaintenanceWindowTask (Maybe Text)
maintenanceWindowTask_maxErrors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowTask' {Maybe Text
maxErrors :: Maybe Text
$sel:maxErrors:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
maxErrors} -> Maybe Text
maxErrors) (\s :: MaintenanceWindowTask
s@MaintenanceWindowTask' {} Maybe Text
a -> MaintenanceWindowTask
s {$sel:maxErrors:MaintenanceWindowTask' :: Maybe Text
maxErrors = Maybe Text
a} :: MaintenanceWindowTask)

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

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

-- | 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.
maintenanceWindowTask_serviceRoleArn :: Lens.Lens' MaintenanceWindowTask (Prelude.Maybe Prelude.Text)
maintenanceWindowTask_serviceRoleArn :: Lens' MaintenanceWindowTask (Maybe Text)
maintenanceWindowTask_serviceRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowTask' {Maybe Text
serviceRoleArn :: Maybe Text
$sel:serviceRoleArn:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
serviceRoleArn} -> Maybe Text
serviceRoleArn) (\s :: MaintenanceWindowTask
s@MaintenanceWindowTask' {} Maybe Text
a -> MaintenanceWindowTask
s {$sel:serviceRoleArn:MaintenanceWindowTask' :: Maybe Text
serviceRoleArn = Maybe Text
a} :: MaintenanceWindowTask)

-- | The targets (either managed nodes or tags). Managed nodes are specified
-- using @Key=instanceids,Values=\<instanceid1>,\<instanceid2>@. Tags are
-- specified using @Key=\<tag name>,Values=\<tag value>@.
maintenanceWindowTask_targets :: Lens.Lens' MaintenanceWindowTask (Prelude.Maybe [Target])
maintenanceWindowTask_targets :: Lens' MaintenanceWindowTask (Maybe [Target])
maintenanceWindowTask_targets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowTask' {Maybe [Target]
targets :: Maybe [Target]
$sel:targets:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe [Target]
targets} -> Maybe [Target]
targets) (\s :: MaintenanceWindowTask
s@MaintenanceWindowTask' {} Maybe [Target]
a -> MaintenanceWindowTask
s {$sel:targets:MaintenanceWindowTask' :: Maybe [Target]
targets = Maybe [Target]
a} :: MaintenanceWindowTask) 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 resource that the task uses during execution. For @RUN_COMMAND@ and
-- @AUTOMATION@ task types, @TaskArn@ is the Amazon Web Services Systems
-- Manager (SSM document) name or ARN. For @LAMBDA@ tasks, it\'s the
-- function name or ARN. For @STEP_FUNCTIONS@ tasks, it\'s the state
-- machine ARN.
maintenanceWindowTask_taskArn :: Lens.Lens' MaintenanceWindowTask (Prelude.Maybe Prelude.Text)
maintenanceWindowTask_taskArn :: Lens' MaintenanceWindowTask (Maybe Text)
maintenanceWindowTask_taskArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowTask' {Maybe Text
taskArn :: Maybe Text
$sel:taskArn:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
taskArn} -> Maybe Text
taskArn) (\s :: MaintenanceWindowTask
s@MaintenanceWindowTask' {} Maybe Text
a -> MaintenanceWindowTask
s {$sel:taskArn:MaintenanceWindowTask' :: Maybe Text
taskArn = Maybe Text
a} :: MaintenanceWindowTask)

-- | The parameters that should be passed to the task when it is run.
--
-- @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.
maintenanceWindowTask_taskParameters :: Lens.Lens' MaintenanceWindowTask (Prelude.Maybe (Prelude.HashMap Prelude.Text MaintenanceWindowTaskParameterValueExpression))
maintenanceWindowTask_taskParameters :: Lens'
  MaintenanceWindowTask
  (Maybe
     (HashMap Text MaintenanceWindowTaskParameterValueExpression))
maintenanceWindowTask_taskParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowTask' {Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
$sel:taskParameters:MaintenanceWindowTask' :: MaintenanceWindowTask
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters} -> Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters) (\s :: MaintenanceWindowTask
s@MaintenanceWindowTask' {} Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
a -> MaintenanceWindowTask
s {$sel:taskParameters:MaintenanceWindowTask' :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters = Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
a} :: MaintenanceWindowTask) 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 type of task.
maintenanceWindowTask_type :: Lens.Lens' MaintenanceWindowTask (Prelude.Maybe MaintenanceWindowTaskType)
maintenanceWindowTask_type :: Lens' MaintenanceWindowTask (Maybe MaintenanceWindowTaskType)
maintenanceWindowTask_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowTask' {Maybe MaintenanceWindowTaskType
type' :: Maybe MaintenanceWindowTaskType
$sel:type':MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe MaintenanceWindowTaskType
type'} -> Maybe MaintenanceWindowTaskType
type') (\s :: MaintenanceWindowTask
s@MaintenanceWindowTask' {} Maybe MaintenanceWindowTaskType
a -> MaintenanceWindowTask
s {$sel:type':MaintenanceWindowTask' :: Maybe MaintenanceWindowTaskType
type' = Maybe MaintenanceWindowTaskType
a} :: MaintenanceWindowTask)

-- | The ID of the maintenance window where the task is registered.
maintenanceWindowTask_windowId :: Lens.Lens' MaintenanceWindowTask (Prelude.Maybe Prelude.Text)
maintenanceWindowTask_windowId :: Lens' MaintenanceWindowTask (Maybe Text)
maintenanceWindowTask_windowId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowTask' {Maybe Text
windowId :: Maybe Text
$sel:windowId:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
windowId} -> Maybe Text
windowId) (\s :: MaintenanceWindowTask
s@MaintenanceWindowTask' {} Maybe Text
a -> MaintenanceWindowTask
s {$sel:windowId:MaintenanceWindowTask' :: Maybe Text
windowId = Maybe Text
a} :: MaintenanceWindowTask)

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

instance Data.FromJSON MaintenanceWindowTask where
  parseJSON :: Value -> Parser MaintenanceWindowTask
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"MaintenanceWindowTask"
      ( \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
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
-> Maybe MaintenanceWindowTaskType
-> Maybe Text
-> Maybe Text
-> MaintenanceWindowTask
MaintenanceWindowTask'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"Targets" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"TaskParameters" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"Type")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"WindowTaskId")
      )

instance Prelude.Hashable MaintenanceWindowTask where
  hashWithSalt :: Int -> MaintenanceWindowTask -> Int
hashWithSalt Int
_salt MaintenanceWindowTask' {Maybe Natural
Maybe [Target]
Maybe Text
Maybe (Sensitive Text)
Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
Maybe AlarmConfiguration
Maybe LoggingInfo
Maybe MaintenanceWindowTaskCutoffBehavior
Maybe MaintenanceWindowTaskType
windowTaskId :: Maybe Text
windowId :: Maybe Text
type' :: Maybe MaintenanceWindowTaskType
taskParameters :: Maybe
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
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:windowTaskId:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
$sel:windowId:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
$sel:type':MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe MaintenanceWindowTaskType
$sel:taskParameters:MaintenanceWindowTask' :: MaintenanceWindowTask
-> Maybe
     (Sensitive
        (HashMap
           Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
$sel:taskArn:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
$sel:targets:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe [Target]
$sel:serviceRoleArn:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
$sel:priority:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Natural
$sel:name:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
$sel:maxErrors:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
$sel:maxConcurrency:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe Text
$sel:loggingInfo:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe LoggingInfo
$sel:description:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe (Sensitive Text)
$sel:cutoffBehavior:MaintenanceWindowTask' :: MaintenanceWindowTask -> Maybe MaintenanceWindowTaskCutoffBehavior
$sel:alarmConfiguration:MaintenanceWindowTask' :: MaintenanceWindowTask -> 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 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
  (Sensitive
     (HashMap
        Text (Sensitive MaintenanceWindowTaskParameterValueExpression)))
taskParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MaintenanceWindowTaskType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
windowId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
windowTaskId

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