{-# 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.GetPatchBaseline
-- 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 patch baseline.
module Amazonka.SSM.GetPatchBaseline
  ( -- * Creating a Request
    GetPatchBaseline (..),
    newGetPatchBaseline,

    -- * Request Lenses
    getPatchBaseline_baselineId,

    -- * Destructuring the Response
    GetPatchBaselineResponse (..),
    newGetPatchBaselineResponse,

    -- * Response Lenses
    getPatchBaselineResponse_approvalRules,
    getPatchBaselineResponse_approvedPatches,
    getPatchBaselineResponse_approvedPatchesComplianceLevel,
    getPatchBaselineResponse_approvedPatchesEnableNonSecurity,
    getPatchBaselineResponse_baselineId,
    getPatchBaselineResponse_createdDate,
    getPatchBaselineResponse_description,
    getPatchBaselineResponse_globalFilters,
    getPatchBaselineResponse_modifiedDate,
    getPatchBaselineResponse_name,
    getPatchBaselineResponse_operatingSystem,
    getPatchBaselineResponse_patchGroups,
    getPatchBaselineResponse_rejectedPatches,
    getPatchBaselineResponse_rejectedPatchesAction,
    getPatchBaselineResponse_sources,
    getPatchBaselineResponse_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:/ 'newGetPatchBaseline' smart constructor.
data GetPatchBaseline = GetPatchBaseline'
  { -- | The ID of the patch baseline to retrieve.
    --
    -- To retrieve information about an Amazon Web Services managed patch
    -- baseline, specify the full Amazon Resource Name (ARN) of the baseline.
    -- For example, for the baseline @AWS-AmazonLinuxDefaultPatchBaseline@,
    -- specify
    -- @arn:aws:ssm:us-east-2:733109147000:patchbaseline\/pb-0e392de35e7c563b7@
    -- instead of @pb-0e392de35e7c563b7@.
    GetPatchBaseline -> Text
baselineId :: Prelude.Text
  }
  deriving (GetPatchBaseline -> GetPatchBaseline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPatchBaseline -> GetPatchBaseline -> Bool
$c/= :: GetPatchBaseline -> GetPatchBaseline -> Bool
== :: GetPatchBaseline -> GetPatchBaseline -> Bool
$c== :: GetPatchBaseline -> GetPatchBaseline -> Bool
Prelude.Eq, ReadPrec [GetPatchBaseline]
ReadPrec GetPatchBaseline
Int -> ReadS GetPatchBaseline
ReadS [GetPatchBaseline]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetPatchBaseline]
$creadListPrec :: ReadPrec [GetPatchBaseline]
readPrec :: ReadPrec GetPatchBaseline
$creadPrec :: ReadPrec GetPatchBaseline
readList :: ReadS [GetPatchBaseline]
$creadList :: ReadS [GetPatchBaseline]
readsPrec :: Int -> ReadS GetPatchBaseline
$creadsPrec :: Int -> ReadS GetPatchBaseline
Prelude.Read, Int -> GetPatchBaseline -> ShowS
[GetPatchBaseline] -> ShowS
GetPatchBaseline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPatchBaseline] -> ShowS
$cshowList :: [GetPatchBaseline] -> ShowS
show :: GetPatchBaseline -> String
$cshow :: GetPatchBaseline -> String
showsPrec :: Int -> GetPatchBaseline -> ShowS
$cshowsPrec :: Int -> GetPatchBaseline -> ShowS
Prelude.Show, forall x. Rep GetPatchBaseline x -> GetPatchBaseline
forall x. GetPatchBaseline -> Rep GetPatchBaseline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPatchBaseline x -> GetPatchBaseline
$cfrom :: forall x. GetPatchBaseline -> Rep GetPatchBaseline x
Prelude.Generic)

-- |
-- Create a value of 'GetPatchBaseline' 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:
--
-- 'baselineId', 'getPatchBaseline_baselineId' - The ID of the patch baseline to retrieve.
--
-- To retrieve information about an Amazon Web Services managed patch
-- baseline, specify the full Amazon Resource Name (ARN) of the baseline.
-- For example, for the baseline @AWS-AmazonLinuxDefaultPatchBaseline@,
-- specify
-- @arn:aws:ssm:us-east-2:733109147000:patchbaseline\/pb-0e392de35e7c563b7@
-- instead of @pb-0e392de35e7c563b7@.
newGetPatchBaseline ::
  -- | 'baselineId'
  Prelude.Text ->
  GetPatchBaseline
newGetPatchBaseline :: Text -> GetPatchBaseline
newGetPatchBaseline Text
pBaselineId_ =
  GetPatchBaseline' {$sel:baselineId:GetPatchBaseline' :: Text
baselineId = Text
pBaselineId_}

-- | The ID of the patch baseline to retrieve.
--
-- To retrieve information about an Amazon Web Services managed patch
-- baseline, specify the full Amazon Resource Name (ARN) of the baseline.
-- For example, for the baseline @AWS-AmazonLinuxDefaultPatchBaseline@,
-- specify
-- @arn:aws:ssm:us-east-2:733109147000:patchbaseline\/pb-0e392de35e7c563b7@
-- instead of @pb-0e392de35e7c563b7@.
getPatchBaseline_baselineId :: Lens.Lens' GetPatchBaseline Prelude.Text
getPatchBaseline_baselineId :: Lens' GetPatchBaseline Text
getPatchBaseline_baselineId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaseline' {Text
baselineId :: Text
$sel:baselineId:GetPatchBaseline' :: GetPatchBaseline -> Text
baselineId} -> Text
baselineId) (\s :: GetPatchBaseline
s@GetPatchBaseline' {} Text
a -> GetPatchBaseline
s {$sel:baselineId:GetPatchBaseline' :: Text
baselineId = Text
a} :: GetPatchBaseline)

instance Core.AWSRequest GetPatchBaseline where
  type
    AWSResponse GetPatchBaseline =
      GetPatchBaselineResponse
  request :: (Service -> Service)
-> GetPatchBaseline -> Request GetPatchBaseline
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 GetPatchBaseline
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetPatchBaseline)))
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 PatchRuleGroup
-> Maybe [Text]
-> Maybe PatchComplianceLevel
-> Maybe Bool
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe PatchFilterGroup
-> Maybe POSIX
-> Maybe Text
-> Maybe OperatingSystem
-> Maybe [Text]
-> Maybe [Text]
-> Maybe PatchAction
-> Maybe [PatchSource]
-> Int
-> GetPatchBaselineResponse
GetPatchBaselineResponse'
            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
"ApprovalRules")
            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
"ApprovedPatches"
                            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
"ApprovedPatchesComplianceLevel")
            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
"ApprovedPatchesEnableNonSecurity")
            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
"BaselineId")
            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
"CreatedDate")
            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
"Description")
            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
"GlobalFilters")
            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
"ModifiedDate")
            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
"Name")
            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
"OperatingSystem")
            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
"PatchGroups" 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
"RejectedPatches"
                            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
"RejectedPatchesAction")
            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
"Sources" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetPatchBaseline where
  hashWithSalt :: Int -> GetPatchBaseline -> Int
hashWithSalt Int
_salt GetPatchBaseline' {Text
baselineId :: Text
$sel:baselineId:GetPatchBaseline' :: GetPatchBaseline -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
baselineId

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

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

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

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

-- | /See:/ 'newGetPatchBaselineResponse' smart constructor.
data GetPatchBaselineResponse = GetPatchBaselineResponse'
  { -- | A set of rules used to include patches in the baseline.
    GetPatchBaselineResponse -> Maybe PatchRuleGroup
approvalRules :: Prelude.Maybe PatchRuleGroup,
    -- | A list of explicitly approved patches for the baseline.
    GetPatchBaselineResponse -> Maybe [Text]
approvedPatches :: Prelude.Maybe [Prelude.Text],
    -- | Returns the specified compliance severity level for approved patches in
    -- the patch baseline.
    GetPatchBaselineResponse -> Maybe PatchComplianceLevel
approvedPatchesComplianceLevel :: Prelude.Maybe PatchComplianceLevel,
    -- | Indicates whether the list of approved patches includes non-security
    -- updates that should be applied to the managed nodes. The default value
    -- is @false@. Applies to Linux managed nodes only.
    GetPatchBaselineResponse -> Maybe Bool
approvedPatchesEnableNonSecurity :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the retrieved patch baseline.
    GetPatchBaselineResponse -> Maybe Text
baselineId :: Prelude.Maybe Prelude.Text,
    -- | The date the patch baseline was created.
    GetPatchBaselineResponse -> Maybe POSIX
createdDate :: Prelude.Maybe Data.POSIX,
    -- | A description of the patch baseline.
    GetPatchBaselineResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A set of global filters used to exclude patches from the baseline.
    GetPatchBaselineResponse -> Maybe PatchFilterGroup
globalFilters :: Prelude.Maybe PatchFilterGroup,
    -- | The date the patch baseline was last modified.
    GetPatchBaselineResponse -> Maybe POSIX
modifiedDate :: Prelude.Maybe Data.POSIX,
    -- | The name of the patch baseline.
    GetPatchBaselineResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Returns the operating system specified for the patch baseline.
    GetPatchBaselineResponse -> Maybe OperatingSystem
operatingSystem :: Prelude.Maybe OperatingSystem,
    -- | Patch groups included in the patch baseline.
    GetPatchBaselineResponse -> Maybe [Text]
patchGroups :: Prelude.Maybe [Prelude.Text],
    -- | A list of explicitly rejected patches for the baseline.
    GetPatchBaselineResponse -> Maybe [Text]
rejectedPatches :: Prelude.Maybe [Prelude.Text],
    -- | The action specified to take on patches included in the
    -- @RejectedPatches@ list. A patch can be allowed only if it is a
    -- dependency of another package, or blocked entirely along with packages
    -- that include it as a dependency.
    GetPatchBaselineResponse -> Maybe PatchAction
rejectedPatchesAction :: Prelude.Maybe PatchAction,
    -- | Information about the patches to use to update the managed nodes,
    -- including target operating systems and source repositories. Applies to
    -- Linux managed nodes only.
    GetPatchBaselineResponse -> Maybe [PatchSource]
sources :: Prelude.Maybe [PatchSource],
    -- | The response's http status code.
    GetPatchBaselineResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetPatchBaselineResponse -> GetPatchBaselineResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPatchBaselineResponse -> GetPatchBaselineResponse -> Bool
$c/= :: GetPatchBaselineResponse -> GetPatchBaselineResponse -> Bool
== :: GetPatchBaselineResponse -> GetPatchBaselineResponse -> Bool
$c== :: GetPatchBaselineResponse -> GetPatchBaselineResponse -> Bool
Prelude.Eq, Int -> GetPatchBaselineResponse -> ShowS
[GetPatchBaselineResponse] -> ShowS
GetPatchBaselineResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPatchBaselineResponse] -> ShowS
$cshowList :: [GetPatchBaselineResponse] -> ShowS
show :: GetPatchBaselineResponse -> String
$cshow :: GetPatchBaselineResponse -> String
showsPrec :: Int -> GetPatchBaselineResponse -> ShowS
$cshowsPrec :: Int -> GetPatchBaselineResponse -> ShowS
Prelude.Show, forall x.
Rep GetPatchBaselineResponse x -> GetPatchBaselineResponse
forall x.
GetPatchBaselineResponse -> Rep GetPatchBaselineResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetPatchBaselineResponse x -> GetPatchBaselineResponse
$cfrom :: forall x.
GetPatchBaselineResponse -> Rep GetPatchBaselineResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetPatchBaselineResponse' 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:
--
-- 'approvalRules', 'getPatchBaselineResponse_approvalRules' - A set of rules used to include patches in the baseline.
--
-- 'approvedPatches', 'getPatchBaselineResponse_approvedPatches' - A list of explicitly approved patches for the baseline.
--
-- 'approvedPatchesComplianceLevel', 'getPatchBaselineResponse_approvedPatchesComplianceLevel' - Returns the specified compliance severity level for approved patches in
-- the patch baseline.
--
-- 'approvedPatchesEnableNonSecurity', 'getPatchBaselineResponse_approvedPatchesEnableNonSecurity' - Indicates whether the list of approved patches includes non-security
-- updates that should be applied to the managed nodes. The default value
-- is @false@. Applies to Linux managed nodes only.
--
-- 'baselineId', 'getPatchBaselineResponse_baselineId' - The ID of the retrieved patch baseline.
--
-- 'createdDate', 'getPatchBaselineResponse_createdDate' - The date the patch baseline was created.
--
-- 'description', 'getPatchBaselineResponse_description' - A description of the patch baseline.
--
-- 'globalFilters', 'getPatchBaselineResponse_globalFilters' - A set of global filters used to exclude patches from the baseline.
--
-- 'modifiedDate', 'getPatchBaselineResponse_modifiedDate' - The date the patch baseline was last modified.
--
-- 'name', 'getPatchBaselineResponse_name' - The name of the patch baseline.
--
-- 'operatingSystem', 'getPatchBaselineResponse_operatingSystem' - Returns the operating system specified for the patch baseline.
--
-- 'patchGroups', 'getPatchBaselineResponse_patchGroups' - Patch groups included in the patch baseline.
--
-- 'rejectedPatches', 'getPatchBaselineResponse_rejectedPatches' - A list of explicitly rejected patches for the baseline.
--
-- 'rejectedPatchesAction', 'getPatchBaselineResponse_rejectedPatchesAction' - The action specified to take on patches included in the
-- @RejectedPatches@ list. A patch can be allowed only if it is a
-- dependency of another package, or blocked entirely along with packages
-- that include it as a dependency.
--
-- 'sources', 'getPatchBaselineResponse_sources' - Information about the patches to use to update the managed nodes,
-- including target operating systems and source repositories. Applies to
-- Linux managed nodes only.
--
-- 'httpStatus', 'getPatchBaselineResponse_httpStatus' - The response's http status code.
newGetPatchBaselineResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetPatchBaselineResponse
newGetPatchBaselineResponse :: Int -> GetPatchBaselineResponse
newGetPatchBaselineResponse Int
pHttpStatus_ =
  GetPatchBaselineResponse'
    { $sel:approvalRules:GetPatchBaselineResponse' :: Maybe PatchRuleGroup
approvalRules =
        forall a. Maybe a
Prelude.Nothing,
      $sel:approvedPatches:GetPatchBaselineResponse' :: Maybe [Text]
approvedPatches = forall a. Maybe a
Prelude.Nothing,
      $sel:approvedPatchesComplianceLevel:GetPatchBaselineResponse' :: Maybe PatchComplianceLevel
approvedPatchesComplianceLevel = forall a. Maybe a
Prelude.Nothing,
      $sel:approvedPatchesEnableNonSecurity:GetPatchBaselineResponse' :: Maybe Bool
approvedPatchesEnableNonSecurity =
        forall a. Maybe a
Prelude.Nothing,
      $sel:baselineId:GetPatchBaselineResponse' :: Maybe Text
baselineId = forall a. Maybe a
Prelude.Nothing,
      $sel:createdDate:GetPatchBaselineResponse' :: Maybe POSIX
createdDate = forall a. Maybe a
Prelude.Nothing,
      $sel:description:GetPatchBaselineResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:globalFilters:GetPatchBaselineResponse' :: Maybe PatchFilterGroup
globalFilters = forall a. Maybe a
Prelude.Nothing,
      $sel:modifiedDate:GetPatchBaselineResponse' :: Maybe POSIX
modifiedDate = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetPatchBaselineResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:operatingSystem:GetPatchBaselineResponse' :: Maybe OperatingSystem
operatingSystem = forall a. Maybe a
Prelude.Nothing,
      $sel:patchGroups:GetPatchBaselineResponse' :: Maybe [Text]
patchGroups = forall a. Maybe a
Prelude.Nothing,
      $sel:rejectedPatches:GetPatchBaselineResponse' :: Maybe [Text]
rejectedPatches = forall a. Maybe a
Prelude.Nothing,
      $sel:rejectedPatchesAction:GetPatchBaselineResponse' :: Maybe PatchAction
rejectedPatchesAction = forall a. Maybe a
Prelude.Nothing,
      $sel:sources:GetPatchBaselineResponse' :: Maybe [PatchSource]
sources = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetPatchBaselineResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A set of rules used to include patches in the baseline.
getPatchBaselineResponse_approvalRules :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe PatchRuleGroup)
getPatchBaselineResponse_approvalRules :: Lens' GetPatchBaselineResponse (Maybe PatchRuleGroup)
getPatchBaselineResponse_approvalRules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe PatchRuleGroup
approvalRules :: Maybe PatchRuleGroup
$sel:approvalRules:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe PatchRuleGroup
approvalRules} -> Maybe PatchRuleGroup
approvalRules) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe PatchRuleGroup
a -> GetPatchBaselineResponse
s {$sel:approvalRules:GetPatchBaselineResponse' :: Maybe PatchRuleGroup
approvalRules = Maybe PatchRuleGroup
a} :: GetPatchBaselineResponse)

-- | A list of explicitly approved patches for the baseline.
getPatchBaselineResponse_approvedPatches :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe [Prelude.Text])
getPatchBaselineResponse_approvedPatches :: Lens' GetPatchBaselineResponse (Maybe [Text])
getPatchBaselineResponse_approvedPatches = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe [Text]
approvedPatches :: Maybe [Text]
$sel:approvedPatches:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe [Text]
approvedPatches} -> Maybe [Text]
approvedPatches) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe [Text]
a -> GetPatchBaselineResponse
s {$sel:approvedPatches:GetPatchBaselineResponse' :: Maybe [Text]
approvedPatches = Maybe [Text]
a} :: GetPatchBaselineResponse) 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

-- | Returns the specified compliance severity level for approved patches in
-- the patch baseline.
getPatchBaselineResponse_approvedPatchesComplianceLevel :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe PatchComplianceLevel)
getPatchBaselineResponse_approvedPatchesComplianceLevel :: Lens' GetPatchBaselineResponse (Maybe PatchComplianceLevel)
getPatchBaselineResponse_approvedPatchesComplianceLevel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe PatchComplianceLevel
approvedPatchesComplianceLevel :: Maybe PatchComplianceLevel
$sel:approvedPatchesComplianceLevel:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe PatchComplianceLevel
approvedPatchesComplianceLevel} -> Maybe PatchComplianceLevel
approvedPatchesComplianceLevel) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe PatchComplianceLevel
a -> GetPatchBaselineResponse
s {$sel:approvedPatchesComplianceLevel:GetPatchBaselineResponse' :: Maybe PatchComplianceLevel
approvedPatchesComplianceLevel = Maybe PatchComplianceLevel
a} :: GetPatchBaselineResponse)

-- | Indicates whether the list of approved patches includes non-security
-- updates that should be applied to the managed nodes. The default value
-- is @false@. Applies to Linux managed nodes only.
getPatchBaselineResponse_approvedPatchesEnableNonSecurity :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe Prelude.Bool)
getPatchBaselineResponse_approvedPatchesEnableNonSecurity :: Lens' GetPatchBaselineResponse (Maybe Bool)
getPatchBaselineResponse_approvedPatchesEnableNonSecurity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe Bool
approvedPatchesEnableNonSecurity :: Maybe Bool
$sel:approvedPatchesEnableNonSecurity:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe Bool
approvedPatchesEnableNonSecurity} -> Maybe Bool
approvedPatchesEnableNonSecurity) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe Bool
a -> GetPatchBaselineResponse
s {$sel:approvedPatchesEnableNonSecurity:GetPatchBaselineResponse' :: Maybe Bool
approvedPatchesEnableNonSecurity = Maybe Bool
a} :: GetPatchBaselineResponse)

-- | The ID of the retrieved patch baseline.
getPatchBaselineResponse_baselineId :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe Prelude.Text)
getPatchBaselineResponse_baselineId :: Lens' GetPatchBaselineResponse (Maybe Text)
getPatchBaselineResponse_baselineId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe Text
baselineId :: Maybe Text
$sel:baselineId:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe Text
baselineId} -> Maybe Text
baselineId) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe Text
a -> GetPatchBaselineResponse
s {$sel:baselineId:GetPatchBaselineResponse' :: Maybe Text
baselineId = Maybe Text
a} :: GetPatchBaselineResponse)

-- | The date the patch baseline was created.
getPatchBaselineResponse_createdDate :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe Prelude.UTCTime)
getPatchBaselineResponse_createdDate :: Lens' GetPatchBaselineResponse (Maybe UTCTime)
getPatchBaselineResponse_createdDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe POSIX
createdDate :: Maybe POSIX
$sel:createdDate:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe POSIX
createdDate} -> Maybe POSIX
createdDate) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe POSIX
a -> GetPatchBaselineResponse
s {$sel:createdDate:GetPatchBaselineResponse' :: Maybe POSIX
createdDate = Maybe POSIX
a} :: GetPatchBaselineResponse) 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

-- | A description of the patch baseline.
getPatchBaselineResponse_description :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe Prelude.Text)
getPatchBaselineResponse_description :: Lens' GetPatchBaselineResponse (Maybe Text)
getPatchBaselineResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe Text
a -> GetPatchBaselineResponse
s {$sel:description:GetPatchBaselineResponse' :: Maybe Text
description = Maybe Text
a} :: GetPatchBaselineResponse)

-- | A set of global filters used to exclude patches from the baseline.
getPatchBaselineResponse_globalFilters :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe PatchFilterGroup)
getPatchBaselineResponse_globalFilters :: Lens' GetPatchBaselineResponse (Maybe PatchFilterGroup)
getPatchBaselineResponse_globalFilters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe PatchFilterGroup
globalFilters :: Maybe PatchFilterGroup
$sel:globalFilters:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe PatchFilterGroup
globalFilters} -> Maybe PatchFilterGroup
globalFilters) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe PatchFilterGroup
a -> GetPatchBaselineResponse
s {$sel:globalFilters:GetPatchBaselineResponse' :: Maybe PatchFilterGroup
globalFilters = Maybe PatchFilterGroup
a} :: GetPatchBaselineResponse)

-- | The date the patch baseline was last modified.
getPatchBaselineResponse_modifiedDate :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe Prelude.UTCTime)
getPatchBaselineResponse_modifiedDate :: Lens' GetPatchBaselineResponse (Maybe UTCTime)
getPatchBaselineResponse_modifiedDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe POSIX
modifiedDate :: Maybe POSIX
$sel:modifiedDate:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe POSIX
modifiedDate} -> Maybe POSIX
modifiedDate) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe POSIX
a -> GetPatchBaselineResponse
s {$sel:modifiedDate:GetPatchBaselineResponse' :: Maybe POSIX
modifiedDate = Maybe POSIX
a} :: GetPatchBaselineResponse) 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 name of the patch baseline.
getPatchBaselineResponse_name :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe Prelude.Text)
getPatchBaselineResponse_name :: Lens' GetPatchBaselineResponse (Maybe Text)
getPatchBaselineResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe Text
a -> GetPatchBaselineResponse
s {$sel:name:GetPatchBaselineResponse' :: Maybe Text
name = Maybe Text
a} :: GetPatchBaselineResponse)

-- | Returns the operating system specified for the patch baseline.
getPatchBaselineResponse_operatingSystem :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe OperatingSystem)
getPatchBaselineResponse_operatingSystem :: Lens' GetPatchBaselineResponse (Maybe OperatingSystem)
getPatchBaselineResponse_operatingSystem = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe OperatingSystem
operatingSystem :: Maybe OperatingSystem
$sel:operatingSystem:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe OperatingSystem
operatingSystem} -> Maybe OperatingSystem
operatingSystem) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe OperatingSystem
a -> GetPatchBaselineResponse
s {$sel:operatingSystem:GetPatchBaselineResponse' :: Maybe OperatingSystem
operatingSystem = Maybe OperatingSystem
a} :: GetPatchBaselineResponse)

-- | Patch groups included in the patch baseline.
getPatchBaselineResponse_patchGroups :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe [Prelude.Text])
getPatchBaselineResponse_patchGroups :: Lens' GetPatchBaselineResponse (Maybe [Text])
getPatchBaselineResponse_patchGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe [Text]
patchGroups :: Maybe [Text]
$sel:patchGroups:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe [Text]
patchGroups} -> Maybe [Text]
patchGroups) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe [Text]
a -> GetPatchBaselineResponse
s {$sel:patchGroups:GetPatchBaselineResponse' :: Maybe [Text]
patchGroups = Maybe [Text]
a} :: GetPatchBaselineResponse) 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

-- | A list of explicitly rejected patches for the baseline.
getPatchBaselineResponse_rejectedPatches :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe [Prelude.Text])
getPatchBaselineResponse_rejectedPatches :: Lens' GetPatchBaselineResponse (Maybe [Text])
getPatchBaselineResponse_rejectedPatches = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe [Text]
rejectedPatches :: Maybe [Text]
$sel:rejectedPatches:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe [Text]
rejectedPatches} -> Maybe [Text]
rejectedPatches) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe [Text]
a -> GetPatchBaselineResponse
s {$sel:rejectedPatches:GetPatchBaselineResponse' :: Maybe [Text]
rejectedPatches = Maybe [Text]
a} :: GetPatchBaselineResponse) 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 action specified to take on patches included in the
-- @RejectedPatches@ list. A patch can be allowed only if it is a
-- dependency of another package, or blocked entirely along with packages
-- that include it as a dependency.
getPatchBaselineResponse_rejectedPatchesAction :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe PatchAction)
getPatchBaselineResponse_rejectedPatchesAction :: Lens' GetPatchBaselineResponse (Maybe PatchAction)
getPatchBaselineResponse_rejectedPatchesAction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe PatchAction
rejectedPatchesAction :: Maybe PatchAction
$sel:rejectedPatchesAction:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe PatchAction
rejectedPatchesAction} -> Maybe PatchAction
rejectedPatchesAction) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe PatchAction
a -> GetPatchBaselineResponse
s {$sel:rejectedPatchesAction:GetPatchBaselineResponse' :: Maybe PatchAction
rejectedPatchesAction = Maybe PatchAction
a} :: GetPatchBaselineResponse)

-- | Information about the patches to use to update the managed nodes,
-- including target operating systems and source repositories. Applies to
-- Linux managed nodes only.
getPatchBaselineResponse_sources :: Lens.Lens' GetPatchBaselineResponse (Prelude.Maybe [PatchSource])
getPatchBaselineResponse_sources :: Lens' GetPatchBaselineResponse (Maybe [PatchSource])
getPatchBaselineResponse_sources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Maybe [PatchSource]
sources :: Maybe [PatchSource]
$sel:sources:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe [PatchSource]
sources} -> Maybe [PatchSource]
sources) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Maybe [PatchSource]
a -> GetPatchBaselineResponse
s {$sel:sources:GetPatchBaselineResponse' :: Maybe [PatchSource]
sources = Maybe [PatchSource]
a} :: GetPatchBaselineResponse) 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 response's http status code.
getPatchBaselineResponse_httpStatus :: Lens.Lens' GetPatchBaselineResponse Prelude.Int
getPatchBaselineResponse_httpStatus :: Lens' GetPatchBaselineResponse Int
getPatchBaselineResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPatchBaselineResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetPatchBaselineResponse
s@GetPatchBaselineResponse' {} Int
a -> GetPatchBaselineResponse
s {$sel:httpStatus:GetPatchBaselineResponse' :: Int
httpStatus = Int
a} :: GetPatchBaselineResponse)

instance Prelude.NFData GetPatchBaselineResponse where
  rnf :: GetPatchBaselineResponse -> ()
rnf GetPatchBaselineResponse' {Int
Maybe Bool
Maybe [Text]
Maybe [PatchSource]
Maybe Text
Maybe POSIX
Maybe OperatingSystem
Maybe PatchAction
Maybe PatchComplianceLevel
Maybe PatchFilterGroup
Maybe PatchRuleGroup
httpStatus :: Int
sources :: Maybe [PatchSource]
rejectedPatchesAction :: Maybe PatchAction
rejectedPatches :: Maybe [Text]
patchGroups :: Maybe [Text]
operatingSystem :: Maybe OperatingSystem
name :: Maybe Text
modifiedDate :: Maybe POSIX
globalFilters :: Maybe PatchFilterGroup
description :: Maybe Text
createdDate :: Maybe POSIX
baselineId :: Maybe Text
approvedPatchesEnableNonSecurity :: Maybe Bool
approvedPatchesComplianceLevel :: Maybe PatchComplianceLevel
approvedPatches :: Maybe [Text]
approvalRules :: Maybe PatchRuleGroup
$sel:httpStatus:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Int
$sel:sources:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe [PatchSource]
$sel:rejectedPatchesAction:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe PatchAction
$sel:rejectedPatches:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe [Text]
$sel:patchGroups:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe [Text]
$sel:operatingSystem:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe OperatingSystem
$sel:name:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe Text
$sel:modifiedDate:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe POSIX
$sel:globalFilters:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe PatchFilterGroup
$sel:description:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe Text
$sel:createdDate:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe POSIX
$sel:baselineId:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe Text
$sel:approvedPatchesEnableNonSecurity:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe Bool
$sel:approvedPatchesComplianceLevel:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe PatchComplianceLevel
$sel:approvedPatches:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe [Text]
$sel:approvalRules:GetPatchBaselineResponse' :: GetPatchBaselineResponse -> Maybe PatchRuleGroup
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe PatchRuleGroup
approvalRules
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
approvedPatches
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PatchComplianceLevel
approvedPatchesComplianceLevel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
approvedPatchesEnableNonSecurity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
baselineId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PatchFilterGroup
globalFilters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
modifiedDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OperatingSystem
operatingSystem
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
patchGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
rejectedPatches
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PatchAction
rejectedPatchesAction
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PatchSource]
sources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus