{-# 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.GetMaintenanceWindowExecution
-- 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 details about a specific a maintenance window execution.
module Amazonka.SSM.GetMaintenanceWindowExecution
  ( -- * Creating a Request
    GetMaintenanceWindowExecution (..),
    newGetMaintenanceWindowExecution,

    -- * Request Lenses
    getMaintenanceWindowExecution_windowExecutionId,

    -- * Destructuring the Response
    GetMaintenanceWindowExecutionResponse (..),
    newGetMaintenanceWindowExecutionResponse,

    -- * Response Lenses
    getMaintenanceWindowExecutionResponse_endTime,
    getMaintenanceWindowExecutionResponse_startTime,
    getMaintenanceWindowExecutionResponse_status,
    getMaintenanceWindowExecutionResponse_statusDetails,
    getMaintenanceWindowExecutionResponse_taskIds,
    getMaintenanceWindowExecutionResponse_windowExecutionId,
    getMaintenanceWindowExecutionResponse_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:/ 'newGetMaintenanceWindowExecution' smart constructor.
data GetMaintenanceWindowExecution = GetMaintenanceWindowExecution'
  { -- | The ID of the maintenance window execution that includes the task.
    GetMaintenanceWindowExecution -> Text
windowExecutionId :: Prelude.Text
  }
  deriving (GetMaintenanceWindowExecution
-> GetMaintenanceWindowExecution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMaintenanceWindowExecution
-> GetMaintenanceWindowExecution -> Bool
$c/= :: GetMaintenanceWindowExecution
-> GetMaintenanceWindowExecution -> Bool
== :: GetMaintenanceWindowExecution
-> GetMaintenanceWindowExecution -> Bool
$c== :: GetMaintenanceWindowExecution
-> GetMaintenanceWindowExecution -> Bool
Prelude.Eq, ReadPrec [GetMaintenanceWindowExecution]
ReadPrec GetMaintenanceWindowExecution
Int -> ReadS GetMaintenanceWindowExecution
ReadS [GetMaintenanceWindowExecution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMaintenanceWindowExecution]
$creadListPrec :: ReadPrec [GetMaintenanceWindowExecution]
readPrec :: ReadPrec GetMaintenanceWindowExecution
$creadPrec :: ReadPrec GetMaintenanceWindowExecution
readList :: ReadS [GetMaintenanceWindowExecution]
$creadList :: ReadS [GetMaintenanceWindowExecution]
readsPrec :: Int -> ReadS GetMaintenanceWindowExecution
$creadsPrec :: Int -> ReadS GetMaintenanceWindowExecution
Prelude.Read, Int -> GetMaintenanceWindowExecution -> ShowS
[GetMaintenanceWindowExecution] -> ShowS
GetMaintenanceWindowExecution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMaintenanceWindowExecution] -> ShowS
$cshowList :: [GetMaintenanceWindowExecution] -> ShowS
show :: GetMaintenanceWindowExecution -> String
$cshow :: GetMaintenanceWindowExecution -> String
showsPrec :: Int -> GetMaintenanceWindowExecution -> ShowS
$cshowsPrec :: Int -> GetMaintenanceWindowExecution -> ShowS
Prelude.Show, forall x.
Rep GetMaintenanceWindowExecution x
-> GetMaintenanceWindowExecution
forall x.
GetMaintenanceWindowExecution
-> Rep GetMaintenanceWindowExecution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetMaintenanceWindowExecution x
-> GetMaintenanceWindowExecution
$cfrom :: forall x.
GetMaintenanceWindowExecution
-> Rep GetMaintenanceWindowExecution x
Prelude.Generic)

-- |
-- Create a value of 'GetMaintenanceWindowExecution' 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', 'getMaintenanceWindowExecution_windowExecutionId' - The ID of the maintenance window execution that includes the task.
newGetMaintenanceWindowExecution ::
  -- | 'windowExecutionId'
  Prelude.Text ->
  GetMaintenanceWindowExecution
newGetMaintenanceWindowExecution :: Text -> GetMaintenanceWindowExecution
newGetMaintenanceWindowExecution Text
pWindowExecutionId_ =
  GetMaintenanceWindowExecution'
    { $sel:windowExecutionId:GetMaintenanceWindowExecution' :: Text
windowExecutionId =
        Text
pWindowExecutionId_
    }

-- | The ID of the maintenance window execution that includes the task.
getMaintenanceWindowExecution_windowExecutionId :: Lens.Lens' GetMaintenanceWindowExecution Prelude.Text
getMaintenanceWindowExecution_windowExecutionId :: Lens' GetMaintenanceWindowExecution Text
getMaintenanceWindowExecution_windowExecutionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecution' {Text
windowExecutionId :: Text
$sel:windowExecutionId:GetMaintenanceWindowExecution' :: GetMaintenanceWindowExecution -> Text
windowExecutionId} -> Text
windowExecutionId) (\s :: GetMaintenanceWindowExecution
s@GetMaintenanceWindowExecution' {} Text
a -> GetMaintenanceWindowExecution
s {$sel:windowExecutionId:GetMaintenanceWindowExecution' :: Text
windowExecutionId = Text
a} :: GetMaintenanceWindowExecution)

instance
  Core.AWSRequest
    GetMaintenanceWindowExecution
  where
  type
    AWSResponse GetMaintenanceWindowExecution =
      GetMaintenanceWindowExecutionResponse
  request :: (Service -> Service)
-> GetMaintenanceWindowExecution
-> Request GetMaintenanceWindowExecution
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 GetMaintenanceWindowExecution
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetMaintenanceWindowExecution)))
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 POSIX
-> Maybe MaintenanceWindowExecutionStatus
-> Maybe Text
-> Maybe [Text]
-> Maybe Text
-> Int
-> GetMaintenanceWindowExecutionResponse
GetMaintenanceWindowExecutionResponse'
            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
"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
"TaskIds" 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
"WindowExecutionId")
            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
    GetMaintenanceWindowExecution
  where
  hashWithSalt :: Int -> GetMaintenanceWindowExecution -> Int
hashWithSalt Int
_salt GetMaintenanceWindowExecution' {Text
windowExecutionId :: Text
$sel:windowExecutionId:GetMaintenanceWindowExecution' :: GetMaintenanceWindowExecution -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
windowExecutionId

instance Prelude.NFData GetMaintenanceWindowExecution where
  rnf :: GetMaintenanceWindowExecution -> ()
rnf GetMaintenanceWindowExecution' {Text
windowExecutionId :: Text
$sel:windowExecutionId:GetMaintenanceWindowExecution' :: GetMaintenanceWindowExecution -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
windowExecutionId

instance Data.ToHeaders GetMaintenanceWindowExecution where
  toHeaders :: GetMaintenanceWindowExecution -> 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.GetMaintenanceWindowExecution" ::
                          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 GetMaintenanceWindowExecution where
  toJSON :: GetMaintenanceWindowExecution -> Value
toJSON GetMaintenanceWindowExecution' {Text
windowExecutionId :: Text
$sel:windowExecutionId:GetMaintenanceWindowExecution' :: GetMaintenanceWindowExecution -> 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)
          ]
      )

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

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

-- | /See:/ 'newGetMaintenanceWindowExecutionResponse' smart constructor.
data GetMaintenanceWindowExecutionResponse = GetMaintenanceWindowExecutionResponse'
  { -- | The time the maintenance window finished running.
    GetMaintenanceWindowExecutionResponse -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | The time the maintenance window started running.
    GetMaintenanceWindowExecutionResponse -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | The status of the maintenance window execution.
    GetMaintenanceWindowExecutionResponse
-> Maybe MaintenanceWindowExecutionStatus
status :: Prelude.Maybe MaintenanceWindowExecutionStatus,
    -- | The details explaining the status. Not available for all status values.
    GetMaintenanceWindowExecutionResponse -> Maybe Text
statusDetails :: Prelude.Maybe Prelude.Text,
    -- | The ID of the task executions from the maintenance window execution.
    GetMaintenanceWindowExecutionResponse -> Maybe [Text]
taskIds :: Prelude.Maybe [Prelude.Text],
    -- | The ID of the maintenance window execution.
    GetMaintenanceWindowExecutionResponse -> Maybe Text
windowExecutionId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetMaintenanceWindowExecutionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetMaintenanceWindowExecutionResponse
-> GetMaintenanceWindowExecutionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMaintenanceWindowExecutionResponse
-> GetMaintenanceWindowExecutionResponse -> Bool
$c/= :: GetMaintenanceWindowExecutionResponse
-> GetMaintenanceWindowExecutionResponse -> Bool
== :: GetMaintenanceWindowExecutionResponse
-> GetMaintenanceWindowExecutionResponse -> Bool
$c== :: GetMaintenanceWindowExecutionResponse
-> GetMaintenanceWindowExecutionResponse -> Bool
Prelude.Eq, ReadPrec [GetMaintenanceWindowExecutionResponse]
ReadPrec GetMaintenanceWindowExecutionResponse
Int -> ReadS GetMaintenanceWindowExecutionResponse
ReadS [GetMaintenanceWindowExecutionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMaintenanceWindowExecutionResponse]
$creadListPrec :: ReadPrec [GetMaintenanceWindowExecutionResponse]
readPrec :: ReadPrec GetMaintenanceWindowExecutionResponse
$creadPrec :: ReadPrec GetMaintenanceWindowExecutionResponse
readList :: ReadS [GetMaintenanceWindowExecutionResponse]
$creadList :: ReadS [GetMaintenanceWindowExecutionResponse]
readsPrec :: Int -> ReadS GetMaintenanceWindowExecutionResponse
$creadsPrec :: Int -> ReadS GetMaintenanceWindowExecutionResponse
Prelude.Read, Int -> GetMaintenanceWindowExecutionResponse -> ShowS
[GetMaintenanceWindowExecutionResponse] -> ShowS
GetMaintenanceWindowExecutionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMaintenanceWindowExecutionResponse] -> ShowS
$cshowList :: [GetMaintenanceWindowExecutionResponse] -> ShowS
show :: GetMaintenanceWindowExecutionResponse -> String
$cshow :: GetMaintenanceWindowExecutionResponse -> String
showsPrec :: Int -> GetMaintenanceWindowExecutionResponse -> ShowS
$cshowsPrec :: Int -> GetMaintenanceWindowExecutionResponse -> ShowS
Prelude.Show, forall x.
Rep GetMaintenanceWindowExecutionResponse x
-> GetMaintenanceWindowExecutionResponse
forall x.
GetMaintenanceWindowExecutionResponse
-> Rep GetMaintenanceWindowExecutionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetMaintenanceWindowExecutionResponse x
-> GetMaintenanceWindowExecutionResponse
$cfrom :: forall x.
GetMaintenanceWindowExecutionResponse
-> Rep GetMaintenanceWindowExecutionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetMaintenanceWindowExecutionResponse' 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', 'getMaintenanceWindowExecutionResponse_endTime' - The time the maintenance window finished running.
--
-- 'startTime', 'getMaintenanceWindowExecutionResponse_startTime' - The time the maintenance window started running.
--
-- 'status', 'getMaintenanceWindowExecutionResponse_status' - The status of the maintenance window execution.
--
-- 'statusDetails', 'getMaintenanceWindowExecutionResponse_statusDetails' - The details explaining the status. Not available for all status values.
--
-- 'taskIds', 'getMaintenanceWindowExecutionResponse_taskIds' - The ID of the task executions from the maintenance window execution.
--
-- 'windowExecutionId', 'getMaintenanceWindowExecutionResponse_windowExecutionId' - The ID of the maintenance window execution.
--
-- 'httpStatus', 'getMaintenanceWindowExecutionResponse_httpStatus' - The response's http status code.
newGetMaintenanceWindowExecutionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetMaintenanceWindowExecutionResponse
newGetMaintenanceWindowExecutionResponse :: Int -> GetMaintenanceWindowExecutionResponse
newGetMaintenanceWindowExecutionResponse Int
pHttpStatus_ =
  GetMaintenanceWindowExecutionResponse'
    { $sel:endTime:GetMaintenanceWindowExecutionResponse' :: Maybe POSIX
endTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:GetMaintenanceWindowExecutionResponse' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:status:GetMaintenanceWindowExecutionResponse' :: Maybe MaintenanceWindowExecutionStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusDetails:GetMaintenanceWindowExecutionResponse' :: Maybe Text
statusDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:taskIds:GetMaintenanceWindowExecutionResponse' :: Maybe [Text]
taskIds = forall a. Maybe a
Prelude.Nothing,
      $sel:windowExecutionId:GetMaintenanceWindowExecutionResponse' :: Maybe Text
windowExecutionId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetMaintenanceWindowExecutionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The time the maintenance window finished running.
getMaintenanceWindowExecutionResponse_endTime :: Lens.Lens' GetMaintenanceWindowExecutionResponse (Prelude.Maybe Prelude.UTCTime)
getMaintenanceWindowExecutionResponse_endTime :: Lens' GetMaintenanceWindowExecutionResponse (Maybe UTCTime)
getMaintenanceWindowExecutionResponse_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionResponse' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: GetMaintenanceWindowExecutionResponse
s@GetMaintenanceWindowExecutionResponse' {} Maybe POSIX
a -> GetMaintenanceWindowExecutionResponse
s {$sel:endTime:GetMaintenanceWindowExecutionResponse' :: Maybe POSIX
endTime = Maybe POSIX
a} :: GetMaintenanceWindowExecutionResponse) 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 time the maintenance window started running.
getMaintenanceWindowExecutionResponse_startTime :: Lens.Lens' GetMaintenanceWindowExecutionResponse (Prelude.Maybe Prelude.UTCTime)
getMaintenanceWindowExecutionResponse_startTime :: Lens' GetMaintenanceWindowExecutionResponse (Maybe UTCTime)
getMaintenanceWindowExecutionResponse_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionResponse' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: GetMaintenanceWindowExecutionResponse
s@GetMaintenanceWindowExecutionResponse' {} Maybe POSIX
a -> GetMaintenanceWindowExecutionResponse
s {$sel:startTime:GetMaintenanceWindowExecutionResponse' :: Maybe POSIX
startTime = Maybe POSIX
a} :: GetMaintenanceWindowExecutionResponse) 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 status of the maintenance window execution.
getMaintenanceWindowExecutionResponse_status :: Lens.Lens' GetMaintenanceWindowExecutionResponse (Prelude.Maybe MaintenanceWindowExecutionStatus)
getMaintenanceWindowExecutionResponse_status :: Lens'
  GetMaintenanceWindowExecutionResponse
  (Maybe MaintenanceWindowExecutionStatus)
getMaintenanceWindowExecutionResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionResponse' {Maybe MaintenanceWindowExecutionStatus
status :: Maybe MaintenanceWindowExecutionStatus
$sel:status:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse
-> Maybe MaintenanceWindowExecutionStatus
status} -> Maybe MaintenanceWindowExecutionStatus
status) (\s :: GetMaintenanceWindowExecutionResponse
s@GetMaintenanceWindowExecutionResponse' {} Maybe MaintenanceWindowExecutionStatus
a -> GetMaintenanceWindowExecutionResponse
s {$sel:status:GetMaintenanceWindowExecutionResponse' :: Maybe MaintenanceWindowExecutionStatus
status = Maybe MaintenanceWindowExecutionStatus
a} :: GetMaintenanceWindowExecutionResponse)

-- | The details explaining the status. Not available for all status values.
getMaintenanceWindowExecutionResponse_statusDetails :: Lens.Lens' GetMaintenanceWindowExecutionResponse (Prelude.Maybe Prelude.Text)
getMaintenanceWindowExecutionResponse_statusDetails :: Lens' GetMaintenanceWindowExecutionResponse (Maybe Text)
getMaintenanceWindowExecutionResponse_statusDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionResponse' {Maybe Text
statusDetails :: Maybe Text
$sel:statusDetails:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse -> Maybe Text
statusDetails} -> Maybe Text
statusDetails) (\s :: GetMaintenanceWindowExecutionResponse
s@GetMaintenanceWindowExecutionResponse' {} Maybe Text
a -> GetMaintenanceWindowExecutionResponse
s {$sel:statusDetails:GetMaintenanceWindowExecutionResponse' :: Maybe Text
statusDetails = Maybe Text
a} :: GetMaintenanceWindowExecutionResponse)

-- | The ID of the task executions from the maintenance window execution.
getMaintenanceWindowExecutionResponse_taskIds :: Lens.Lens' GetMaintenanceWindowExecutionResponse (Prelude.Maybe [Prelude.Text])
getMaintenanceWindowExecutionResponse_taskIds :: Lens' GetMaintenanceWindowExecutionResponse (Maybe [Text])
getMaintenanceWindowExecutionResponse_taskIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionResponse' {Maybe [Text]
taskIds :: Maybe [Text]
$sel:taskIds:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse -> Maybe [Text]
taskIds} -> Maybe [Text]
taskIds) (\s :: GetMaintenanceWindowExecutionResponse
s@GetMaintenanceWindowExecutionResponse' {} Maybe [Text]
a -> GetMaintenanceWindowExecutionResponse
s {$sel:taskIds:GetMaintenanceWindowExecutionResponse' :: Maybe [Text]
taskIds = Maybe [Text]
a} :: GetMaintenanceWindowExecutionResponse) 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 ID of the maintenance window execution.
getMaintenanceWindowExecutionResponse_windowExecutionId :: Lens.Lens' GetMaintenanceWindowExecutionResponse (Prelude.Maybe Prelude.Text)
getMaintenanceWindowExecutionResponse_windowExecutionId :: Lens' GetMaintenanceWindowExecutionResponse (Maybe Text)
getMaintenanceWindowExecutionResponse_windowExecutionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMaintenanceWindowExecutionResponse' {Maybe Text
windowExecutionId :: Maybe Text
$sel:windowExecutionId:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse -> Maybe Text
windowExecutionId} -> Maybe Text
windowExecutionId) (\s :: GetMaintenanceWindowExecutionResponse
s@GetMaintenanceWindowExecutionResponse' {} Maybe Text
a -> GetMaintenanceWindowExecutionResponse
s {$sel:windowExecutionId:GetMaintenanceWindowExecutionResponse' :: Maybe Text
windowExecutionId = Maybe Text
a} :: GetMaintenanceWindowExecutionResponse)

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

instance
  Prelude.NFData
    GetMaintenanceWindowExecutionResponse
  where
  rnf :: GetMaintenanceWindowExecutionResponse -> ()
rnf GetMaintenanceWindowExecutionResponse' {Int
Maybe [Text]
Maybe Text
Maybe POSIX
Maybe MaintenanceWindowExecutionStatus
httpStatus :: Int
windowExecutionId :: Maybe Text
taskIds :: Maybe [Text]
statusDetails :: Maybe Text
status :: Maybe MaintenanceWindowExecutionStatus
startTime :: Maybe POSIX
endTime :: Maybe POSIX
$sel:httpStatus:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse -> Int
$sel:windowExecutionId:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse -> Maybe Text
$sel:taskIds:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse -> Maybe [Text]
$sel:statusDetails:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse -> Maybe Text
$sel:status:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse
-> Maybe MaintenanceWindowExecutionStatus
$sel:startTime:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse -> Maybe POSIX
$sel:endTime:GetMaintenanceWindowExecutionResponse' :: GetMaintenanceWindowExecutionResponse -> 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 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]
taskIds
      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 Int
httpStatus