{-# 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.MaintenanceWindowExecution
-- 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.MaintenanceWindowExecution 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.MaintenanceWindowExecutionStatus

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

-- |
-- Create a value of 'MaintenanceWindowExecution' 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', 'maintenanceWindowExecution_endTime' - The time the execution finished.
--
-- 'startTime', 'maintenanceWindowExecution_startTime' - The time the execution started.
--
-- 'status', 'maintenanceWindowExecution_status' - The status of the execution.
--
-- 'statusDetails', 'maintenanceWindowExecution_statusDetails' - The details explaining the status. Not available for all status values.
--
-- 'windowExecutionId', 'maintenanceWindowExecution_windowExecutionId' - The ID of the maintenance window execution.
--
-- 'windowId', 'maintenanceWindowExecution_windowId' - The ID of the maintenance window.
newMaintenanceWindowExecution ::
  MaintenanceWindowExecution
newMaintenanceWindowExecution :: MaintenanceWindowExecution
newMaintenanceWindowExecution =
  MaintenanceWindowExecution'
    { $sel:endTime:MaintenanceWindowExecution' :: Maybe POSIX
endTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:MaintenanceWindowExecution' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:status:MaintenanceWindowExecution' :: Maybe MaintenanceWindowExecutionStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusDetails:MaintenanceWindowExecution' :: Maybe Text
statusDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:windowExecutionId:MaintenanceWindowExecution' :: Maybe Text
windowExecutionId = forall a. Maybe a
Prelude.Nothing,
      $sel:windowId:MaintenanceWindowExecution' :: Maybe Text
windowId = forall a. Maybe a
Prelude.Nothing
    }

-- | The time the execution finished.
maintenanceWindowExecution_endTime :: Lens.Lens' MaintenanceWindowExecution (Prelude.Maybe Prelude.UTCTime)
maintenanceWindowExecution_endTime :: Lens' MaintenanceWindowExecution (Maybe UTCTime)
maintenanceWindowExecution_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowExecution' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: MaintenanceWindowExecution
s@MaintenanceWindowExecution' {} Maybe POSIX
a -> MaintenanceWindowExecution
s {$sel:endTime:MaintenanceWindowExecution' :: Maybe POSIX
endTime = Maybe POSIX
a} :: MaintenanceWindowExecution) 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 execution started.
maintenanceWindowExecution_startTime :: Lens.Lens' MaintenanceWindowExecution (Prelude.Maybe Prelude.UTCTime)
maintenanceWindowExecution_startTime :: Lens' MaintenanceWindowExecution (Maybe UTCTime)
maintenanceWindowExecution_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowExecution' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: MaintenanceWindowExecution
s@MaintenanceWindowExecution' {} Maybe POSIX
a -> MaintenanceWindowExecution
s {$sel:startTime:MaintenanceWindowExecution' :: Maybe POSIX
startTime = Maybe POSIX
a} :: MaintenanceWindowExecution) 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 execution.
maintenanceWindowExecution_status :: Lens.Lens' MaintenanceWindowExecution (Prelude.Maybe MaintenanceWindowExecutionStatus)
maintenanceWindowExecution_status :: Lens'
  MaintenanceWindowExecution (Maybe MaintenanceWindowExecutionStatus)
maintenanceWindowExecution_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MaintenanceWindowExecution' {Maybe MaintenanceWindowExecutionStatus
status :: Maybe MaintenanceWindowExecutionStatus
$sel:status:MaintenanceWindowExecution' :: MaintenanceWindowExecution
-> Maybe MaintenanceWindowExecutionStatus
status} -> Maybe MaintenanceWindowExecutionStatus
status) (\s :: MaintenanceWindowExecution
s@MaintenanceWindowExecution' {} Maybe MaintenanceWindowExecutionStatus
a -> MaintenanceWindowExecution
s {$sel:status:MaintenanceWindowExecution' :: Maybe MaintenanceWindowExecutionStatus
status = Maybe MaintenanceWindowExecutionStatus
a} :: MaintenanceWindowExecution)

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

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

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

instance Data.FromJSON MaintenanceWindowExecution where
  parseJSON :: Value -> Parser MaintenanceWindowExecution
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"MaintenanceWindowExecution"
      ( \Object
x ->
          Maybe POSIX
-> Maybe POSIX
-> Maybe MaintenanceWindowExecutionStatus
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> MaintenanceWindowExecution
MaintenanceWindowExecution'
            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
"EndTime")
            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
"StartTime")
            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
"Status")
            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
"StatusDetails")
            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
"WindowExecutionId")
            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")
      )

instance Prelude.Hashable MaintenanceWindowExecution where
  hashWithSalt :: Int -> MaintenanceWindowExecution -> Int
hashWithSalt Int
_salt MaintenanceWindowExecution' {Maybe Text
Maybe POSIX
Maybe MaintenanceWindowExecutionStatus
windowId :: Maybe Text
windowExecutionId :: Maybe Text
statusDetails :: Maybe Text
status :: Maybe MaintenanceWindowExecutionStatus
startTime :: Maybe POSIX
endTime :: Maybe POSIX
$sel:windowId:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> Maybe Text
$sel:windowExecutionId:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> Maybe Text
$sel:statusDetails:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> Maybe Text
$sel:status:MaintenanceWindowExecution' :: MaintenanceWindowExecution
-> Maybe MaintenanceWindowExecutionStatus
$sel:startTime:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> Maybe POSIX
$sel:endTime:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MaintenanceWindowExecutionStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
statusDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
windowExecutionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
windowId

instance Prelude.NFData MaintenanceWindowExecution where
  rnf :: MaintenanceWindowExecution -> ()
rnf MaintenanceWindowExecution' {Maybe Text
Maybe POSIX
Maybe MaintenanceWindowExecutionStatus
windowId :: Maybe Text
windowExecutionId :: Maybe Text
statusDetails :: Maybe Text
status :: Maybe MaintenanceWindowExecutionStatus
startTime :: Maybe POSIX
endTime :: Maybe POSIX
$sel:windowId:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> Maybe Text
$sel:windowExecutionId:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> Maybe Text
$sel:statusDetails:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> Maybe Text
$sel:status:MaintenanceWindowExecution' :: MaintenanceWindowExecution
-> Maybe MaintenanceWindowExecutionStatus
$sel:startTime:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> Maybe POSIX
$sel:endTime:MaintenanceWindowExecution' :: MaintenanceWindowExecution -> 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
windowExecutionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
windowId