{-# 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.EffectivePatch
-- 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.EffectivePatch 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.Patch
import Amazonka.SSM.Types.PatchStatus

-- | The @EffectivePatch@ structure defines metadata about a patch along with
-- the approval state of the patch in a particular patch baseline. The
-- approval state includes information about whether the patch is currently
-- approved, due to be approved by a rule, explicitly approved, or
-- explicitly rejected and the date the patch was or will be approved.
--
-- /See:/ 'newEffectivePatch' smart constructor.
data EffectivePatch = EffectivePatch'
  { -- | Provides metadata for a patch, including information such as the KB ID,
    -- severity, classification and a URL for where more information can be
    -- obtained about the patch.
    EffectivePatch -> Maybe Patch
patch :: Prelude.Maybe Patch,
    -- | The status of the patch in a patch baseline. This includes information
    -- about whether the patch is currently approved, due to be approved by a
    -- rule, explicitly approved, or explicitly rejected and the date the patch
    -- was or will be approved.
    EffectivePatch -> Maybe PatchStatus
patchStatus :: Prelude.Maybe PatchStatus
  }
  deriving (EffectivePatch -> EffectivePatch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EffectivePatch -> EffectivePatch -> Bool
$c/= :: EffectivePatch -> EffectivePatch -> Bool
== :: EffectivePatch -> EffectivePatch -> Bool
$c== :: EffectivePatch -> EffectivePatch -> Bool
Prelude.Eq, ReadPrec [EffectivePatch]
ReadPrec EffectivePatch
Int -> ReadS EffectivePatch
ReadS [EffectivePatch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EffectivePatch]
$creadListPrec :: ReadPrec [EffectivePatch]
readPrec :: ReadPrec EffectivePatch
$creadPrec :: ReadPrec EffectivePatch
readList :: ReadS [EffectivePatch]
$creadList :: ReadS [EffectivePatch]
readsPrec :: Int -> ReadS EffectivePatch
$creadsPrec :: Int -> ReadS EffectivePatch
Prelude.Read, Int -> EffectivePatch -> ShowS
[EffectivePatch] -> ShowS
EffectivePatch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EffectivePatch] -> ShowS
$cshowList :: [EffectivePatch] -> ShowS
show :: EffectivePatch -> String
$cshow :: EffectivePatch -> String
showsPrec :: Int -> EffectivePatch -> ShowS
$cshowsPrec :: Int -> EffectivePatch -> ShowS
Prelude.Show, forall x. Rep EffectivePatch x -> EffectivePatch
forall x. EffectivePatch -> Rep EffectivePatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EffectivePatch x -> EffectivePatch
$cfrom :: forall x. EffectivePatch -> Rep EffectivePatch x
Prelude.Generic)

-- |
-- Create a value of 'EffectivePatch' 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:
--
-- 'patch', 'effectivePatch_patch' - Provides metadata for a patch, including information such as the KB ID,
-- severity, classification and a URL for where more information can be
-- obtained about the patch.
--
-- 'patchStatus', 'effectivePatch_patchStatus' - The status of the patch in a patch baseline. This includes information
-- about whether the patch is currently approved, due to be approved by a
-- rule, explicitly approved, or explicitly rejected and the date the patch
-- was or will be approved.
newEffectivePatch ::
  EffectivePatch
newEffectivePatch :: EffectivePatch
newEffectivePatch =
  EffectivePatch'
    { $sel:patch:EffectivePatch' :: Maybe Patch
patch = forall a. Maybe a
Prelude.Nothing,
      $sel:patchStatus:EffectivePatch' :: Maybe PatchStatus
patchStatus = forall a. Maybe a
Prelude.Nothing
    }

-- | Provides metadata for a patch, including information such as the KB ID,
-- severity, classification and a URL for where more information can be
-- obtained about the patch.
effectivePatch_patch :: Lens.Lens' EffectivePatch (Prelude.Maybe Patch)
effectivePatch_patch :: Lens' EffectivePatch (Maybe Patch)
effectivePatch_patch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EffectivePatch' {Maybe Patch
patch :: Maybe Patch
$sel:patch:EffectivePatch' :: EffectivePatch -> Maybe Patch
patch} -> Maybe Patch
patch) (\s :: EffectivePatch
s@EffectivePatch' {} Maybe Patch
a -> EffectivePatch
s {$sel:patch:EffectivePatch' :: Maybe Patch
patch = Maybe Patch
a} :: EffectivePatch)

-- | The status of the patch in a patch baseline. This includes information
-- about whether the patch is currently approved, due to be approved by a
-- rule, explicitly approved, or explicitly rejected and the date the patch
-- was or will be approved.
effectivePatch_patchStatus :: Lens.Lens' EffectivePatch (Prelude.Maybe PatchStatus)
effectivePatch_patchStatus :: Lens' EffectivePatch (Maybe PatchStatus)
effectivePatch_patchStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EffectivePatch' {Maybe PatchStatus
patchStatus :: Maybe PatchStatus
$sel:patchStatus:EffectivePatch' :: EffectivePatch -> Maybe PatchStatus
patchStatus} -> Maybe PatchStatus
patchStatus) (\s :: EffectivePatch
s@EffectivePatch' {} Maybe PatchStatus
a -> EffectivePatch
s {$sel:patchStatus:EffectivePatch' :: Maybe PatchStatus
patchStatus = Maybe PatchStatus
a} :: EffectivePatch)

instance Data.FromJSON EffectivePatch where
  parseJSON :: Value -> Parser EffectivePatch
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"EffectivePatch"
      ( \Object
x ->
          Maybe Patch -> Maybe PatchStatus -> EffectivePatch
EffectivePatch'
            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
"Patch")
            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
"PatchStatus")
      )

instance Prelude.Hashable EffectivePatch where
  hashWithSalt :: Int -> EffectivePatch -> Int
hashWithSalt Int
_salt EffectivePatch' {Maybe Patch
Maybe PatchStatus
patchStatus :: Maybe PatchStatus
patch :: Maybe Patch
$sel:patchStatus:EffectivePatch' :: EffectivePatch -> Maybe PatchStatus
$sel:patch:EffectivePatch' :: EffectivePatch -> Maybe Patch
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Patch
patch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PatchStatus
patchStatus

instance Prelude.NFData EffectivePatch where
  rnf :: EffectivePatch -> ()
rnf EffectivePatch' {Maybe Patch
Maybe PatchStatus
patchStatus :: Maybe PatchStatus
patch :: Maybe Patch
$sel:patchStatus:EffectivePatch' :: EffectivePatch -> Maybe PatchStatus
$sel:patch:EffectivePatch' :: EffectivePatch -> Maybe Patch
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Patch
patch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PatchStatus
patchStatus