{-# 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.GetMaintenanceWindowExecutionTaskInvocation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about a specific task running on a specific
-- target.
module Amazonka.SSM.GetMaintenanceWindowExecutionTaskInvocation
  ( -- * Creating a Request
    GetMaintenanceWindowExecutionTaskInvocation (..),
    newGetMaintenanceWindowExecutionTaskInvocation,

    -- * Request Lenses
    getMaintenanceWindowExecutionTaskInvocation_windowExecutionId,
    getMaintenanceWindowExecutionTaskInvocation_taskId,
    getMaintenanceWindowExecutionTaskInvocation_invocationId,

    -- * Destructuring the Response
    GetMaintenanceWindowExecutionTaskInvocationResponse (..),
    newGetMaintenanceWindowExecutionTaskInvocationResponse,

    -- * Response Lenses
    getMaintenanceWindowExecutionTaskInvocationResponse_endTime,
    getMaintenanceWindowExecutionTaskInvocationResponse_executionId,
    getMaintenanceWindowExecutionTaskInvocationResponse_invocationId,
    getMaintenanceWindowExecutionTaskInvocationResponse_ownerInformation,
    getMaintenanceWindowExecutionTaskInvocationResponse_parameters,
    getMaintenanceWindowExecutionTaskInvocationResponse_startTime,
    getMaintenanceWindowExecutionTaskInvocationResponse_status,
    getMaintenanceWindowExecutionTaskInvocationResponse_statusDetails,
    getMaintenanceWindowExecutionTaskInvocationResponse_taskExecutionId,
    getMaintenanceWindowExecutionTaskInvocationResponse_taskType,
    getMaintenanceWindowExecutionTaskInvocationResponse_windowExecutionId,
    getMaintenanceWindowExecutionTaskInvocationResponse_windowTargetId,
    getMaintenanceWindowExecutionTaskInvocationResponse_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:/ 'newGetMaintenanceWindowExecutionTaskInvocation' smart constructor.
data GetMaintenanceWindowExecutionTaskInvocation = GetMaintenanceWindowExecutionTaskInvocation'
  { -- | The ID of the maintenance window execution for which the task is a part.
    GetMaintenanceWindowExecutionTaskInvocation -> Text
windowExecutionId :: Prelude.Text,
    -- | The ID of the specific task in the maintenance window task that should
    -- be retrieved.
    GetMaintenanceWindowExecutionTaskInvocation -> Text
taskId :: Prelude.Text,
    -- | The invocation ID to retrieve.
    GetMaintenanceWindowExecutionTaskInvocation -> Text
invocationId :: Prelude.Text
  }
  deriving (GetMaintenanceWindowExecutionTaskInvocation
-> GetMaintenanceWindowExecutionTaskInvocation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMaintenanceWindowExecutionTaskInvocation
-> GetMaintenanceWindowExecutionTaskInvocation -> Bool
$c/= :: GetMaintenanceWindowExecutionTaskInvocation
-> GetMaintenanceWindowExecutionTaskInvocation -> Bool
== :: GetMaintenanceWindowExecutionTaskInvocation
-> GetMaintenanceWindowExecutionTaskInvocation -> Bool
$c== :: GetMaintenanceWindowExecutionTaskInvocation
-> GetMaintenanceWindowExecutionTaskInvocation -> Bool
Prelude.Eq, ReadPrec [GetMaintenanceWindowExecutionTaskInvocation]
ReadPrec GetMaintenanceWindowExecutionTaskInvocation
Int -> ReadS GetMaintenanceWindowExecutionTaskInvocation
ReadS [GetMaintenanceWindowExecutionTaskInvocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMaintenanceWindowExecutionTaskInvocation]
$creadListPrec :: ReadPrec [GetMaintenanceWindowExecutionTaskInvocation]
readPrec :: ReadPrec GetMaintenanceWindowExecutionTaskInvocation
$creadPrec :: ReadPrec GetMaintenanceWindowExecutionTaskInvocation
readList :: ReadS [GetMaintenanceWindowExecutionTaskInvocation]
$creadList :: ReadS [GetMaintenanceWindowExecutionTaskInvocation]
readsPrec :: Int -> ReadS GetMaintenanceWindowExecutionTaskInvocation
$creadsPrec :: Int -> ReadS GetMaintenanceWindowExecutionTaskInvocation
Prelude.Read, Int -> GetMaintenanceWindowExecutionTaskInvocation -> ShowS
[GetMaintenanceWindowExecutionTaskInvocation] -> ShowS
GetMaintenanceWindowExecutionTaskInvocation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMaintenanceWindowExecutionTaskInvocation] -> ShowS
$cshowList :: [GetMaintenanceWindowExecutionTaskInvocation] -> ShowS
show :: GetMaintenanceWindowExecutionTaskInvocation -> String
$cshow :: GetMaintenanceWindowExecutionTaskInvocation -> String
showsPrec :: Int -> GetMaintenanceWindowExecutionTaskInvocation -> ShowS
$cshowsPrec :: Int -> GetMaintenanceWindowExecutionTaskInvocation -> ShowS
Prelude.Show, forall x.
Rep GetMaintenanceWindowExecutionTaskInvocation x
-> GetMaintenanceWindowExecutionTaskInvocation
forall x.
GetMaintenanceWindowExecutionTaskInvocation
-> Rep GetMaintenanceWindowExecutionTaskInvocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetMaintenanceWindowExecutionTaskInvocation x
-> GetMaintenanceWindowExecutionTaskInvocation
$cfrom :: forall x.
GetMaintenanceWindowExecutionTaskInvocation
-> Rep GetMaintenanceWindowExecutionTaskInvocation x
Prelude.Generic)

-- |
-- Create a value of 'GetMaintenanceWindowExecutionTaskInvocation' 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:
--
-- 'windowExecutionId', 'getMaintenanceWindowExecutionTaskInvocation_windowExecutionId' - The ID of the maintenance window execution for which the task is a part.
--
-- 'taskId', 'getMaintenanceWindowExecutionTaskInvocation_taskId' - The ID of the specific task in the maintenance window task that should
-- be retrieved.
--
-- 'invocationId', 'getMaintenanceWindowExecutionTaskInvocation_invocationId' - The invocation ID to retrieve.
newGetMaintenanceWindowExecutionTaskInvocation ::
  -- | 'windowExecutionId'
  Prelude.Text ->
  -- | 'taskId'
  Prelude.Text ->
  -- | 'invocationId'
  Prelude.Text ->
  GetMaintenanceWindowExecutionTaskInvocation
newGetMaintenanceWindowExecutionTaskInvocation :: Text -> Text -> Text -> GetMaintenanceWindowExecutionTaskInvocation
newGetMaintenanceWindowExecutionTaskInvocation
  Text
pWindowExecutionId_
  Text
pTaskId_
  Text
pInvocationId_ =
    GetMaintenanceWindowExecutionTaskInvocation'
      { $sel:windowExecutionId:GetMaintenanceWindowExecutionTaskInvocation' :: Text
windowExecutionId =
          Text
pWindowExecutionId_,
        $sel:taskId:GetMaintenanceWindowExecutionTaskInvocation' :: Text
taskId = Text
pTaskId_,
        $sel:invocationId:GetMaintenanceWindowExecutionTaskInvocation' :: Text
invocationId = Text
pInvocationId_
      }

-- | The ID of the maintenance window execution for which the task is a part.
getMaintenanceWindowExecutionTaskInvocation_windowExecutionId :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocation Prelude.Text
getMaintenanceWindowExecutionTaskInvocation_windowExecutionId :: Lens' GetMaintenanceWindowExecutionTaskInvocation Text
getMaintenanceWindowExecutionTaskInvocation_windowExecutionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocation' {Text
windowExecutionId :: Text
$sel:windowExecutionId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
windowExecutionId} -> Text
windowExecutionId) (\s :: GetMaintenanceWindowExecutionTaskInvocation
s@GetMaintenanceWindowExecutionTaskInvocation' {} Text
a -> GetMaintenanceWindowExecutionTaskInvocation
s {$sel:windowExecutionId:GetMaintenanceWindowExecutionTaskInvocation' :: Text
windowExecutionId = Text
a} :: GetMaintenanceWindowExecutionTaskInvocation)

-- | The ID of the specific task in the maintenance window task that should
-- be retrieved.
getMaintenanceWindowExecutionTaskInvocation_taskId :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocation Prelude.Text
getMaintenanceWindowExecutionTaskInvocation_taskId :: Lens' GetMaintenanceWindowExecutionTaskInvocation Text
getMaintenanceWindowExecutionTaskInvocation_taskId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocation' {Text
taskId :: Text
$sel:taskId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
taskId} -> Text
taskId) (\s :: GetMaintenanceWindowExecutionTaskInvocation
s@GetMaintenanceWindowExecutionTaskInvocation' {} Text
a -> GetMaintenanceWindowExecutionTaskInvocation
s {$sel:taskId:GetMaintenanceWindowExecutionTaskInvocation' :: Text
taskId = Text
a} :: GetMaintenanceWindowExecutionTaskInvocation)

-- | The invocation ID to retrieve.
getMaintenanceWindowExecutionTaskInvocation_invocationId :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocation Prelude.Text
getMaintenanceWindowExecutionTaskInvocation_invocationId :: Lens' GetMaintenanceWindowExecutionTaskInvocation Text
getMaintenanceWindowExecutionTaskInvocation_invocationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocation' {Text
invocationId :: Text
$sel:invocationId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
invocationId} -> Text
invocationId) (\s :: GetMaintenanceWindowExecutionTaskInvocation
s@GetMaintenanceWindowExecutionTaskInvocation' {} Text
a -> GetMaintenanceWindowExecutionTaskInvocation
s {$sel:invocationId:GetMaintenanceWindowExecutionTaskInvocation' :: Text
invocationId = Text
a} :: GetMaintenanceWindowExecutionTaskInvocation)

instance
  Core.AWSRequest
    GetMaintenanceWindowExecutionTaskInvocation
  where
  type
    AWSResponse
      GetMaintenanceWindowExecutionTaskInvocation =
      GetMaintenanceWindowExecutionTaskInvocationResponse
  request :: (Service -> Service)
-> GetMaintenanceWindowExecutionTaskInvocation
-> Request GetMaintenanceWindowExecutionTaskInvocation
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 GetMaintenanceWindowExecutionTaskInvocation
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse GetMaintenanceWindowExecutionTaskInvocation)))
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 POSIX
-> Maybe Text
-> Maybe Text
-> Maybe (Sensitive Text)
-> Maybe (Sensitive Text)
-> Maybe POSIX
-> Maybe MaintenanceWindowExecutionStatus
-> Maybe Text
-> Maybe Text
-> Maybe MaintenanceWindowTaskType
-> Maybe Text
-> Maybe Text
-> Int
-> GetMaintenanceWindowExecutionTaskInvocationResponse
GetMaintenanceWindowExecutionTaskInvocationResponse'
            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
"EndTime")
            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
"ExecutionId")
            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
"InvocationId")
            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
"OwnerInformation")
            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
"Parameters")
            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
"StartTime")
            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
"Status")
            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
"StatusDetails")
            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
"TaskExecutionId")
            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
"TaskType")
            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
"WindowExecutionId")
            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
"WindowTargetId")
            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
    GetMaintenanceWindowExecutionTaskInvocation
  where
  hashWithSalt :: Int -> GetMaintenanceWindowExecutionTaskInvocation -> Int
hashWithSalt
    Int
_salt
    GetMaintenanceWindowExecutionTaskInvocation' {Text
invocationId :: Text
taskId :: Text
windowExecutionId :: Text
$sel:invocationId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
$sel:taskId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
$sel:windowExecutionId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
windowExecutionId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
taskId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
invocationId

instance
  Prelude.NFData
    GetMaintenanceWindowExecutionTaskInvocation
  where
  rnf :: GetMaintenanceWindowExecutionTaskInvocation -> ()
rnf GetMaintenanceWindowExecutionTaskInvocation' {Text
invocationId :: Text
taskId :: Text
windowExecutionId :: Text
$sel:invocationId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
$sel:taskId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
$sel:windowExecutionId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
windowExecutionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
taskId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
invocationId

instance
  Data.ToHeaders
    GetMaintenanceWindowExecutionTaskInvocation
  where
  toHeaders :: GetMaintenanceWindowExecutionTaskInvocation -> 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.GetMaintenanceWindowExecutionTaskInvocation" ::
                          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
    GetMaintenanceWindowExecutionTaskInvocation
  where
  toJSON :: GetMaintenanceWindowExecutionTaskInvocation -> Value
toJSON
    GetMaintenanceWindowExecutionTaskInvocation' {Text
invocationId :: Text
taskId :: Text
windowExecutionId :: Text
$sel:invocationId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
$sel:taskId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
$sel:windowExecutionId:GetMaintenanceWindowExecutionTaskInvocation' :: GetMaintenanceWindowExecutionTaskInvocation -> Text
..} =
      [Pair] -> Value
Data.object
        ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
            [ forall a. a -> Maybe a
Prelude.Just
                (Key
"WindowExecutionId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
windowExecutionId),
              forall a. a -> Maybe a
Prelude.Just (Key
"TaskId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
taskId),
              forall a. a -> Maybe a
Prelude.Just (Key
"InvocationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
invocationId)
            ]
        )

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

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

-- | /See:/ 'newGetMaintenanceWindowExecutionTaskInvocationResponse' smart constructor.
data GetMaintenanceWindowExecutionTaskInvocationResponse = GetMaintenanceWindowExecutionTaskInvocationResponse'
  { -- | The time that the task finished running on the target.
    GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | The execution ID.
    GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
executionId :: Prelude.Maybe Prelude.Text,
    -- | The invocation ID.
    GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
invocationId :: Prelude.Maybe Prelude.Text,
    -- | User-provided value to be included in any Amazon CloudWatch Events or
    -- Amazon EventBridge events raised while running tasks for these targets
    -- in this maintenance window.
    GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe (Sensitive Text)
ownerInformation :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The parameters used at the time that the task ran.
    GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe (Sensitive Text)
parameters :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The time that the task started running on the target.
    GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | The task status for an invocation.
    GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe MaintenanceWindowExecutionStatus
status :: Prelude.Maybe MaintenanceWindowExecutionStatus,
    -- | The details explaining the status. Details are only available for
    -- certain status values.
    GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
statusDetails :: Prelude.Maybe Prelude.Text,
    -- | The task execution ID.
    GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
taskExecutionId :: Prelude.Maybe Prelude.Text,
    -- | Retrieves the task type for a maintenance window.
    GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe MaintenanceWindowTaskType
taskType :: Prelude.Maybe MaintenanceWindowTaskType,
    -- | The maintenance window execution ID.
    GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
windowExecutionId :: Prelude.Maybe Prelude.Text,
    -- | The maintenance window target ID.
    GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
windowTargetId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetMaintenanceWindowExecutionTaskInvocationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetMaintenanceWindowExecutionTaskInvocationResponse
-> GetMaintenanceWindowExecutionTaskInvocationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> GetMaintenanceWindowExecutionTaskInvocationResponse -> Bool
$c/= :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> GetMaintenanceWindowExecutionTaskInvocationResponse -> Bool
== :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> GetMaintenanceWindowExecutionTaskInvocationResponse -> Bool
$c== :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> GetMaintenanceWindowExecutionTaskInvocationResponse -> Bool
Prelude.Eq, Int -> GetMaintenanceWindowExecutionTaskInvocationResponse -> ShowS
[GetMaintenanceWindowExecutionTaskInvocationResponse] -> ShowS
GetMaintenanceWindowExecutionTaskInvocationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMaintenanceWindowExecutionTaskInvocationResponse] -> ShowS
$cshowList :: [GetMaintenanceWindowExecutionTaskInvocationResponse] -> ShowS
show :: GetMaintenanceWindowExecutionTaskInvocationResponse -> String
$cshow :: GetMaintenanceWindowExecutionTaskInvocationResponse -> String
showsPrec :: Int -> GetMaintenanceWindowExecutionTaskInvocationResponse -> ShowS
$cshowsPrec :: Int -> GetMaintenanceWindowExecutionTaskInvocationResponse -> ShowS
Prelude.Show, forall x.
Rep GetMaintenanceWindowExecutionTaskInvocationResponse x
-> GetMaintenanceWindowExecutionTaskInvocationResponse
forall x.
GetMaintenanceWindowExecutionTaskInvocationResponse
-> Rep GetMaintenanceWindowExecutionTaskInvocationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetMaintenanceWindowExecutionTaskInvocationResponse x
-> GetMaintenanceWindowExecutionTaskInvocationResponse
$cfrom :: forall x.
GetMaintenanceWindowExecutionTaskInvocationResponse
-> Rep GetMaintenanceWindowExecutionTaskInvocationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetMaintenanceWindowExecutionTaskInvocationResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'endTime', 'getMaintenanceWindowExecutionTaskInvocationResponse_endTime' - The time that the task finished running on the target.
--
-- 'executionId', 'getMaintenanceWindowExecutionTaskInvocationResponse_executionId' - The execution ID.
--
-- 'invocationId', 'getMaintenanceWindowExecutionTaskInvocationResponse_invocationId' - The invocation ID.
--
-- 'ownerInformation', 'getMaintenanceWindowExecutionTaskInvocationResponse_ownerInformation' - User-provided value to be included in any Amazon CloudWatch Events or
-- Amazon EventBridge events raised while running tasks for these targets
-- in this maintenance window.
--
-- 'parameters', 'getMaintenanceWindowExecutionTaskInvocationResponse_parameters' - The parameters used at the time that the task ran.
--
-- 'startTime', 'getMaintenanceWindowExecutionTaskInvocationResponse_startTime' - The time that the task started running on the target.
--
-- 'status', 'getMaintenanceWindowExecutionTaskInvocationResponse_status' - The task status for an invocation.
--
-- 'statusDetails', 'getMaintenanceWindowExecutionTaskInvocationResponse_statusDetails' - The details explaining the status. Details are only available for
-- certain status values.
--
-- 'taskExecutionId', 'getMaintenanceWindowExecutionTaskInvocationResponse_taskExecutionId' - The task execution ID.
--
-- 'taskType', 'getMaintenanceWindowExecutionTaskInvocationResponse_taskType' - Retrieves the task type for a maintenance window.
--
-- 'windowExecutionId', 'getMaintenanceWindowExecutionTaskInvocationResponse_windowExecutionId' - The maintenance window execution ID.
--
-- 'windowTargetId', 'getMaintenanceWindowExecutionTaskInvocationResponse_windowTargetId' - The maintenance window target ID.
--
-- 'httpStatus', 'getMaintenanceWindowExecutionTaskInvocationResponse_httpStatus' - The response's http status code.
newGetMaintenanceWindowExecutionTaskInvocationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetMaintenanceWindowExecutionTaskInvocationResponse
newGetMaintenanceWindowExecutionTaskInvocationResponse :: Int -> GetMaintenanceWindowExecutionTaskInvocationResponse
newGetMaintenanceWindowExecutionTaskInvocationResponse
  Int
pHttpStatus_ =
    GetMaintenanceWindowExecutionTaskInvocationResponse'
      { $sel:endTime:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe POSIX
endTime =
          forall a. Maybe a
Prelude.Nothing,
        $sel:executionId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe Text
executionId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:invocationId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe Text
invocationId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:ownerInformation:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe (Sensitive Text)
ownerInformation =
          forall a. Maybe a
Prelude.Nothing,
        $sel:parameters:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe (Sensitive Text)
parameters =
          forall a. Maybe a
Prelude.Nothing,
        $sel:startTime:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe POSIX
startTime =
          forall a. Maybe a
Prelude.Nothing,
        $sel:status:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe MaintenanceWindowExecutionStatus
status =
          forall a. Maybe a
Prelude.Nothing,
        $sel:statusDetails:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe Text
statusDetails =
          forall a. Maybe a
Prelude.Nothing,
        $sel:taskExecutionId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe Text
taskExecutionId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:taskType:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe MaintenanceWindowTaskType
taskType =
          forall a. Maybe a
Prelude.Nothing,
        $sel:windowExecutionId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe Text
windowExecutionId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:windowTargetId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe Text
windowTargetId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

-- | The time that the task finished running on the target.
getMaintenanceWindowExecutionTaskInvocationResponse_endTime :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocationResponse (Prelude.Maybe Prelude.UTCTime)
getMaintenanceWindowExecutionTaskInvocationResponse_endTime :: Lens'
  GetMaintenanceWindowExecutionTaskInvocationResponse (Maybe UTCTime)
getMaintenanceWindowExecutionTaskInvocationResponse_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocationResponse' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: GetMaintenanceWindowExecutionTaskInvocationResponse
s@GetMaintenanceWindowExecutionTaskInvocationResponse' {} Maybe POSIX
a -> GetMaintenanceWindowExecutionTaskInvocationResponse
s {$sel:endTime:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe POSIX
endTime = Maybe POSIX
a} :: GetMaintenanceWindowExecutionTaskInvocationResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The execution ID.
getMaintenanceWindowExecutionTaskInvocationResponse_executionId :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocationResponse (Prelude.Maybe Prelude.Text)
getMaintenanceWindowExecutionTaskInvocationResponse_executionId :: Lens'
  GetMaintenanceWindowExecutionTaskInvocationResponse (Maybe Text)
getMaintenanceWindowExecutionTaskInvocationResponse_executionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocationResponse' {Maybe Text
executionId :: Maybe Text
$sel:executionId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
executionId} -> Maybe Text
executionId) (\s :: GetMaintenanceWindowExecutionTaskInvocationResponse
s@GetMaintenanceWindowExecutionTaskInvocationResponse' {} Maybe Text
a -> GetMaintenanceWindowExecutionTaskInvocationResponse
s {$sel:executionId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe Text
executionId = Maybe Text
a} :: GetMaintenanceWindowExecutionTaskInvocationResponse)

-- | The invocation ID.
getMaintenanceWindowExecutionTaskInvocationResponse_invocationId :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocationResponse (Prelude.Maybe Prelude.Text)
getMaintenanceWindowExecutionTaskInvocationResponse_invocationId :: Lens'
  GetMaintenanceWindowExecutionTaskInvocationResponse (Maybe Text)
getMaintenanceWindowExecutionTaskInvocationResponse_invocationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocationResponse' {Maybe Text
invocationId :: Maybe Text
$sel:invocationId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
invocationId} -> Maybe Text
invocationId) (\s :: GetMaintenanceWindowExecutionTaskInvocationResponse
s@GetMaintenanceWindowExecutionTaskInvocationResponse' {} Maybe Text
a -> GetMaintenanceWindowExecutionTaskInvocationResponse
s {$sel:invocationId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe Text
invocationId = Maybe Text
a} :: GetMaintenanceWindowExecutionTaskInvocationResponse)

-- | User-provided value to be included in any Amazon CloudWatch Events or
-- Amazon EventBridge events raised while running tasks for these targets
-- in this maintenance window.
getMaintenanceWindowExecutionTaskInvocationResponse_ownerInformation :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocationResponse (Prelude.Maybe Prelude.Text)
getMaintenanceWindowExecutionTaskInvocationResponse_ownerInformation :: Lens'
  GetMaintenanceWindowExecutionTaskInvocationResponse (Maybe Text)
getMaintenanceWindowExecutionTaskInvocationResponse_ownerInformation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocationResponse' {Maybe (Sensitive Text)
ownerInformation :: Maybe (Sensitive Text)
$sel:ownerInformation:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe (Sensitive Text)
ownerInformation} -> Maybe (Sensitive Text)
ownerInformation) (\s :: GetMaintenanceWindowExecutionTaskInvocationResponse
s@GetMaintenanceWindowExecutionTaskInvocationResponse' {} Maybe (Sensitive Text)
a -> GetMaintenanceWindowExecutionTaskInvocationResponse
s {$sel:ownerInformation:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe (Sensitive Text)
ownerInformation = Maybe (Sensitive Text)
a} :: GetMaintenanceWindowExecutionTaskInvocationResponse) 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 parameters used at the time that the task ran.
getMaintenanceWindowExecutionTaskInvocationResponse_parameters :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocationResponse (Prelude.Maybe Prelude.Text)
getMaintenanceWindowExecutionTaskInvocationResponse_parameters :: Lens'
  GetMaintenanceWindowExecutionTaskInvocationResponse (Maybe Text)
getMaintenanceWindowExecutionTaskInvocationResponse_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocationResponse' {Maybe (Sensitive Text)
parameters :: Maybe (Sensitive Text)
$sel:parameters:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe (Sensitive Text)
parameters} -> Maybe (Sensitive Text)
parameters) (\s :: GetMaintenanceWindowExecutionTaskInvocationResponse
s@GetMaintenanceWindowExecutionTaskInvocationResponse' {} Maybe (Sensitive Text)
a -> GetMaintenanceWindowExecutionTaskInvocationResponse
s {$sel:parameters:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe (Sensitive Text)
parameters = Maybe (Sensitive Text)
a} :: GetMaintenanceWindowExecutionTaskInvocationResponse) 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 time that the task started running on the target.
getMaintenanceWindowExecutionTaskInvocationResponse_startTime :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocationResponse (Prelude.Maybe Prelude.UTCTime)
getMaintenanceWindowExecutionTaskInvocationResponse_startTime :: Lens'
  GetMaintenanceWindowExecutionTaskInvocationResponse (Maybe UTCTime)
getMaintenanceWindowExecutionTaskInvocationResponse_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocationResponse' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: GetMaintenanceWindowExecutionTaskInvocationResponse
s@GetMaintenanceWindowExecutionTaskInvocationResponse' {} Maybe POSIX
a -> GetMaintenanceWindowExecutionTaskInvocationResponse
s {$sel:startTime:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe POSIX
startTime = Maybe POSIX
a} :: GetMaintenanceWindowExecutionTaskInvocationResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The task status for an invocation.
getMaintenanceWindowExecutionTaskInvocationResponse_status :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocationResponse (Prelude.Maybe MaintenanceWindowExecutionStatus)
getMaintenanceWindowExecutionTaskInvocationResponse_status :: Lens'
  GetMaintenanceWindowExecutionTaskInvocationResponse
  (Maybe MaintenanceWindowExecutionStatus)
getMaintenanceWindowExecutionTaskInvocationResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocationResponse' {Maybe MaintenanceWindowExecutionStatus
status :: Maybe MaintenanceWindowExecutionStatus
$sel:status:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe MaintenanceWindowExecutionStatus
status} -> Maybe MaintenanceWindowExecutionStatus
status) (\s :: GetMaintenanceWindowExecutionTaskInvocationResponse
s@GetMaintenanceWindowExecutionTaskInvocationResponse' {} Maybe MaintenanceWindowExecutionStatus
a -> GetMaintenanceWindowExecutionTaskInvocationResponse
s {$sel:status:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe MaintenanceWindowExecutionStatus
status = Maybe MaintenanceWindowExecutionStatus
a} :: GetMaintenanceWindowExecutionTaskInvocationResponse)

-- | The details explaining the status. Details are only available for
-- certain status values.
getMaintenanceWindowExecutionTaskInvocationResponse_statusDetails :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocationResponse (Prelude.Maybe Prelude.Text)
getMaintenanceWindowExecutionTaskInvocationResponse_statusDetails :: Lens'
  GetMaintenanceWindowExecutionTaskInvocationResponse (Maybe Text)
getMaintenanceWindowExecutionTaskInvocationResponse_statusDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocationResponse' {Maybe Text
statusDetails :: Maybe Text
$sel:statusDetails:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
statusDetails} -> Maybe Text
statusDetails) (\s :: GetMaintenanceWindowExecutionTaskInvocationResponse
s@GetMaintenanceWindowExecutionTaskInvocationResponse' {} Maybe Text
a -> GetMaintenanceWindowExecutionTaskInvocationResponse
s {$sel:statusDetails:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe Text
statusDetails = Maybe Text
a} :: GetMaintenanceWindowExecutionTaskInvocationResponse)

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

-- | Retrieves the task type for a maintenance window.
getMaintenanceWindowExecutionTaskInvocationResponse_taskType :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocationResponse (Prelude.Maybe MaintenanceWindowTaskType)
getMaintenanceWindowExecutionTaskInvocationResponse_taskType :: Lens'
  GetMaintenanceWindowExecutionTaskInvocationResponse
  (Maybe MaintenanceWindowTaskType)
getMaintenanceWindowExecutionTaskInvocationResponse_taskType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocationResponse' {Maybe MaintenanceWindowTaskType
taskType :: Maybe MaintenanceWindowTaskType
$sel:taskType:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe MaintenanceWindowTaskType
taskType} -> Maybe MaintenanceWindowTaskType
taskType) (\s :: GetMaintenanceWindowExecutionTaskInvocationResponse
s@GetMaintenanceWindowExecutionTaskInvocationResponse' {} Maybe MaintenanceWindowTaskType
a -> GetMaintenanceWindowExecutionTaskInvocationResponse
s {$sel:taskType:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe MaintenanceWindowTaskType
taskType = Maybe MaintenanceWindowTaskType
a} :: GetMaintenanceWindowExecutionTaskInvocationResponse)

-- | The maintenance window execution ID.
getMaintenanceWindowExecutionTaskInvocationResponse_windowExecutionId :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocationResponse (Prelude.Maybe Prelude.Text)
getMaintenanceWindowExecutionTaskInvocationResponse_windowExecutionId :: Lens'
  GetMaintenanceWindowExecutionTaskInvocationResponse (Maybe Text)
getMaintenanceWindowExecutionTaskInvocationResponse_windowExecutionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocationResponse' {Maybe Text
windowExecutionId :: Maybe Text
$sel:windowExecutionId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
windowExecutionId} -> Maybe Text
windowExecutionId) (\s :: GetMaintenanceWindowExecutionTaskInvocationResponse
s@GetMaintenanceWindowExecutionTaskInvocationResponse' {} Maybe Text
a -> GetMaintenanceWindowExecutionTaskInvocationResponse
s {$sel:windowExecutionId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe Text
windowExecutionId = Maybe Text
a} :: GetMaintenanceWindowExecutionTaskInvocationResponse)

-- | The maintenance window target ID.
getMaintenanceWindowExecutionTaskInvocationResponse_windowTargetId :: Lens.Lens' GetMaintenanceWindowExecutionTaskInvocationResponse (Prelude.Maybe Prelude.Text)
getMaintenanceWindowExecutionTaskInvocationResponse_windowTargetId :: Lens'
  GetMaintenanceWindowExecutionTaskInvocationResponse (Maybe Text)
getMaintenanceWindowExecutionTaskInvocationResponse_windowTargetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionTaskInvocationResponse' {Maybe Text
windowTargetId :: Maybe Text
$sel:windowTargetId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
windowTargetId} -> Maybe Text
windowTargetId) (\s :: GetMaintenanceWindowExecutionTaskInvocationResponse
s@GetMaintenanceWindowExecutionTaskInvocationResponse' {} Maybe Text
a -> GetMaintenanceWindowExecutionTaskInvocationResponse
s {$sel:windowTargetId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: Maybe Text
windowTargetId = Maybe Text
a} :: GetMaintenanceWindowExecutionTaskInvocationResponse)

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

instance
  Prelude.NFData
    GetMaintenanceWindowExecutionTaskInvocationResponse
  where
  rnf :: GetMaintenanceWindowExecutionTaskInvocationResponse -> ()
rnf
    GetMaintenanceWindowExecutionTaskInvocationResponse' {Int
Maybe Text
Maybe (Sensitive Text)
Maybe POSIX
Maybe MaintenanceWindowExecutionStatus
Maybe MaintenanceWindowTaskType
httpStatus :: Int
windowTargetId :: Maybe Text
windowExecutionId :: Maybe Text
taskType :: Maybe MaintenanceWindowTaskType
taskExecutionId :: Maybe Text
statusDetails :: Maybe Text
status :: Maybe MaintenanceWindowExecutionStatus
startTime :: Maybe POSIX
parameters :: Maybe (Sensitive Text)
ownerInformation :: Maybe (Sensitive Text)
invocationId :: Maybe Text
executionId :: Maybe Text
endTime :: Maybe POSIX
$sel:httpStatus:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Int
$sel:windowTargetId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
$sel:windowExecutionId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
$sel:taskType:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe MaintenanceWindowTaskType
$sel:taskExecutionId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
$sel:statusDetails:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
$sel:status:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe MaintenanceWindowExecutionStatus
$sel:startTime:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe POSIX
$sel:parameters:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe (Sensitive Text)
$sel:ownerInformation:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse
-> Maybe (Sensitive Text)
$sel:invocationId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
$sel:executionId:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe Text
$sel:endTime:GetMaintenanceWindowExecutionTaskInvocationResponse' :: GetMaintenanceWindowExecutionTaskInvocationResponse -> Maybe POSIX
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executionId
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
invocationId
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
ownerInformation
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
parameters
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startTime
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MaintenanceWindowExecutionStatus
status
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusDetails
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
taskExecutionId
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MaintenanceWindowTaskType
taskType
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
windowExecutionId
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
windowTargetId
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus