{-# 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.MGN.Types.LifeCycleLastTest
-- 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.MGN.Types.LifeCycleLastTest where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MGN.Types.LifeCycleLastTestFinalized
import Amazonka.MGN.Types.LifeCycleLastTestInitiated
import Amazonka.MGN.Types.LifeCycleLastTestReverted
import qualified Amazonka.Prelude as Prelude

-- | Lifecycle last Test.
--
-- /See:/ 'newLifeCycleLastTest' smart constructor.
data LifeCycleLastTest = LifeCycleLastTest'
  { -- | Lifecycle last Test finalized.
    LifeCycleLastTest -> Maybe LifeCycleLastTestFinalized
finalized :: Prelude.Maybe LifeCycleLastTestFinalized,
    -- | Lifecycle last Test initiated.
    LifeCycleLastTest -> Maybe LifeCycleLastTestInitiated
initiated :: Prelude.Maybe LifeCycleLastTestInitiated,
    -- | Lifecycle last Test reverted.
    LifeCycleLastTest -> Maybe LifeCycleLastTestReverted
reverted :: Prelude.Maybe LifeCycleLastTestReverted
  }
  deriving (LifeCycleLastTest -> LifeCycleLastTest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LifeCycleLastTest -> LifeCycleLastTest -> Bool
$c/= :: LifeCycleLastTest -> LifeCycleLastTest -> Bool
== :: LifeCycleLastTest -> LifeCycleLastTest -> Bool
$c== :: LifeCycleLastTest -> LifeCycleLastTest -> Bool
Prelude.Eq, ReadPrec [LifeCycleLastTest]
ReadPrec LifeCycleLastTest
Int -> ReadS LifeCycleLastTest
ReadS [LifeCycleLastTest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LifeCycleLastTest]
$creadListPrec :: ReadPrec [LifeCycleLastTest]
readPrec :: ReadPrec LifeCycleLastTest
$creadPrec :: ReadPrec LifeCycleLastTest
readList :: ReadS [LifeCycleLastTest]
$creadList :: ReadS [LifeCycleLastTest]
readsPrec :: Int -> ReadS LifeCycleLastTest
$creadsPrec :: Int -> ReadS LifeCycleLastTest
Prelude.Read, Int -> LifeCycleLastTest -> ShowS
[LifeCycleLastTest] -> ShowS
LifeCycleLastTest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LifeCycleLastTest] -> ShowS
$cshowList :: [LifeCycleLastTest] -> ShowS
show :: LifeCycleLastTest -> String
$cshow :: LifeCycleLastTest -> String
showsPrec :: Int -> LifeCycleLastTest -> ShowS
$cshowsPrec :: Int -> LifeCycleLastTest -> ShowS
Prelude.Show, forall x. Rep LifeCycleLastTest x -> LifeCycleLastTest
forall x. LifeCycleLastTest -> Rep LifeCycleLastTest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LifeCycleLastTest x -> LifeCycleLastTest
$cfrom :: forall x. LifeCycleLastTest -> Rep LifeCycleLastTest x
Prelude.Generic)

-- |
-- Create a value of 'LifeCycleLastTest' 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:
--
-- 'finalized', 'lifeCycleLastTest_finalized' - Lifecycle last Test finalized.
--
-- 'initiated', 'lifeCycleLastTest_initiated' - Lifecycle last Test initiated.
--
-- 'reverted', 'lifeCycleLastTest_reverted' - Lifecycle last Test reverted.
newLifeCycleLastTest ::
  LifeCycleLastTest
newLifeCycleLastTest :: LifeCycleLastTest
newLifeCycleLastTest =
  LifeCycleLastTest'
    { $sel:finalized:LifeCycleLastTest' :: Maybe LifeCycleLastTestFinalized
finalized = forall a. Maybe a
Prelude.Nothing,
      $sel:initiated:LifeCycleLastTest' :: Maybe LifeCycleLastTestInitiated
initiated = forall a. Maybe a
Prelude.Nothing,
      $sel:reverted:LifeCycleLastTest' :: Maybe LifeCycleLastTestReverted
reverted = forall a. Maybe a
Prelude.Nothing
    }

-- | Lifecycle last Test finalized.
lifeCycleLastTest_finalized :: Lens.Lens' LifeCycleLastTest (Prelude.Maybe LifeCycleLastTestFinalized)
lifeCycleLastTest_finalized :: Lens' LifeCycleLastTest (Maybe LifeCycleLastTestFinalized)
lifeCycleLastTest_finalized = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LifeCycleLastTest' {Maybe LifeCycleLastTestFinalized
finalized :: Maybe LifeCycleLastTestFinalized
$sel:finalized:LifeCycleLastTest' :: LifeCycleLastTest -> Maybe LifeCycleLastTestFinalized
finalized} -> Maybe LifeCycleLastTestFinalized
finalized) (\s :: LifeCycleLastTest
s@LifeCycleLastTest' {} Maybe LifeCycleLastTestFinalized
a -> LifeCycleLastTest
s {$sel:finalized:LifeCycleLastTest' :: Maybe LifeCycleLastTestFinalized
finalized = Maybe LifeCycleLastTestFinalized
a} :: LifeCycleLastTest)

-- | Lifecycle last Test initiated.
lifeCycleLastTest_initiated :: Lens.Lens' LifeCycleLastTest (Prelude.Maybe LifeCycleLastTestInitiated)
lifeCycleLastTest_initiated :: Lens' LifeCycleLastTest (Maybe LifeCycleLastTestInitiated)
lifeCycleLastTest_initiated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LifeCycleLastTest' {Maybe LifeCycleLastTestInitiated
initiated :: Maybe LifeCycleLastTestInitiated
$sel:initiated:LifeCycleLastTest' :: LifeCycleLastTest -> Maybe LifeCycleLastTestInitiated
initiated} -> Maybe LifeCycleLastTestInitiated
initiated) (\s :: LifeCycleLastTest
s@LifeCycleLastTest' {} Maybe LifeCycleLastTestInitiated
a -> LifeCycleLastTest
s {$sel:initiated:LifeCycleLastTest' :: Maybe LifeCycleLastTestInitiated
initiated = Maybe LifeCycleLastTestInitiated
a} :: LifeCycleLastTest)

-- | Lifecycle last Test reverted.
lifeCycleLastTest_reverted :: Lens.Lens' LifeCycleLastTest (Prelude.Maybe LifeCycleLastTestReverted)
lifeCycleLastTest_reverted :: Lens' LifeCycleLastTest (Maybe LifeCycleLastTestReverted)
lifeCycleLastTest_reverted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LifeCycleLastTest' {Maybe LifeCycleLastTestReverted
reverted :: Maybe LifeCycleLastTestReverted
$sel:reverted:LifeCycleLastTest' :: LifeCycleLastTest -> Maybe LifeCycleLastTestReverted
reverted} -> Maybe LifeCycleLastTestReverted
reverted) (\s :: LifeCycleLastTest
s@LifeCycleLastTest' {} Maybe LifeCycleLastTestReverted
a -> LifeCycleLastTest
s {$sel:reverted:LifeCycleLastTest' :: Maybe LifeCycleLastTestReverted
reverted = Maybe LifeCycleLastTestReverted
a} :: LifeCycleLastTest)

instance Data.FromJSON LifeCycleLastTest where
  parseJSON :: Value -> Parser LifeCycleLastTest
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"LifeCycleLastTest"
      ( \Object
x ->
          Maybe LifeCycleLastTestFinalized
-> Maybe LifeCycleLastTestInitiated
-> Maybe LifeCycleLastTestReverted
-> LifeCycleLastTest
LifeCycleLastTest'
            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
"finalized")
            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
"initiated")
            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
"reverted")
      )

instance Prelude.Hashable LifeCycleLastTest where
  hashWithSalt :: Int -> LifeCycleLastTest -> Int
hashWithSalt Int
_salt LifeCycleLastTest' {Maybe LifeCycleLastTestFinalized
Maybe LifeCycleLastTestInitiated
Maybe LifeCycleLastTestReverted
reverted :: Maybe LifeCycleLastTestReverted
initiated :: Maybe LifeCycleLastTestInitiated
finalized :: Maybe LifeCycleLastTestFinalized
$sel:reverted:LifeCycleLastTest' :: LifeCycleLastTest -> Maybe LifeCycleLastTestReverted
$sel:initiated:LifeCycleLastTest' :: LifeCycleLastTest -> Maybe LifeCycleLastTestInitiated
$sel:finalized:LifeCycleLastTest' :: LifeCycleLastTest -> Maybe LifeCycleLastTestFinalized
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LifeCycleLastTestFinalized
finalized
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LifeCycleLastTestInitiated
initiated
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LifeCycleLastTestReverted
reverted

instance Prelude.NFData LifeCycleLastTest where
  rnf :: LifeCycleLastTest -> ()
rnf LifeCycleLastTest' {Maybe LifeCycleLastTestFinalized
Maybe LifeCycleLastTestInitiated
Maybe LifeCycleLastTestReverted
reverted :: Maybe LifeCycleLastTestReverted
initiated :: Maybe LifeCycleLastTestInitiated
finalized :: Maybe LifeCycleLastTestFinalized
$sel:reverted:LifeCycleLastTest' :: LifeCycleLastTest -> Maybe LifeCycleLastTestReverted
$sel:initiated:LifeCycleLastTest' :: LifeCycleLastTest -> Maybe LifeCycleLastTestInitiated
$sel:finalized:LifeCycleLastTest' :: LifeCycleLastTest -> Maybe LifeCycleLastTestFinalized
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe LifeCycleLastTestFinalized
finalized
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LifeCycleLastTestInitiated
initiated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LifeCycleLastTestReverted
reverted