module Stratosphere.SSM.PatchBaseline (
module Exports, PatchBaseline(..), mkPatchBaseline
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.SSM.PatchBaseline.PatchFilterGroupProperty as Exports
import {-# SOURCE #-} Stratosphere.SSM.PatchBaseline.PatchSourceProperty as Exports
import {-# SOURCE #-} Stratosphere.SSM.PatchBaseline.RuleGroupProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data PatchBaseline
=
PatchBaseline {PatchBaseline -> ()
haddock_workaround_ :: (),
PatchBaseline -> Maybe RuleGroupProperty
approvalRules :: (Prelude.Maybe RuleGroupProperty),
PatchBaseline -> Maybe (ValueList Text)
approvedPatches :: (Prelude.Maybe (ValueList Prelude.Text)),
PatchBaseline -> Maybe (Value Text)
approvedPatchesComplianceLevel :: (Prelude.Maybe (Value Prelude.Text)),
PatchBaseline -> Maybe (Value Bool)
approvedPatchesEnableNonSecurity :: (Prelude.Maybe (Value Prelude.Bool)),
PatchBaseline -> Maybe (Value Text)
availableSecurityUpdatesComplianceStatus :: (Prelude.Maybe (Value Prelude.Text)),
PatchBaseline -> Maybe (Value Bool)
defaultBaseline :: (Prelude.Maybe (Value Prelude.Bool)),
PatchBaseline -> Maybe (Value Text)
description :: (Prelude.Maybe (Value Prelude.Text)),
PatchBaseline -> Maybe PatchFilterGroupProperty
globalFilters :: (Prelude.Maybe PatchFilterGroupProperty),
PatchBaseline -> Value Text
name :: (Value Prelude.Text),
PatchBaseline -> Maybe (Value Text)
operatingSystem :: (Prelude.Maybe (Value Prelude.Text)),
PatchBaseline -> Maybe (ValueList Text)
patchGroups :: (Prelude.Maybe (ValueList Prelude.Text)),
PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: (Prelude.Maybe (ValueList Prelude.Text)),
PatchBaseline -> Maybe (Value Text)
rejectedPatchesAction :: (Prelude.Maybe (Value Prelude.Text)),
PatchBaseline -> Maybe [PatchSourceProperty]
sources :: (Prelude.Maybe [PatchSourceProperty]),
PatchBaseline -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag])}
deriving stock (PatchBaseline -> PatchBaseline -> Bool
(PatchBaseline -> PatchBaseline -> Bool)
-> (PatchBaseline -> PatchBaseline -> Bool) -> Eq PatchBaseline
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PatchBaseline -> PatchBaseline -> Bool
== :: PatchBaseline -> PatchBaseline -> Bool
$c/= :: PatchBaseline -> PatchBaseline -> Bool
/= :: PatchBaseline -> PatchBaseline -> Bool
Prelude.Eq, Int -> PatchBaseline -> ShowS
[PatchBaseline] -> ShowS
PatchBaseline -> String
(Int -> PatchBaseline -> ShowS)
-> (PatchBaseline -> String)
-> ([PatchBaseline] -> ShowS)
-> Show PatchBaseline
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PatchBaseline -> ShowS
showsPrec :: Int -> PatchBaseline -> ShowS
$cshow :: PatchBaseline -> String
show :: PatchBaseline -> String
$cshowList :: [PatchBaseline] -> ShowS
showList :: [PatchBaseline] -> ShowS
Prelude.Show)
mkPatchBaseline :: Value Prelude.Text -> PatchBaseline
mkPatchBaseline :: Value Text -> PatchBaseline
mkPatchBaseline Value Text
name
= PatchBaseline
{haddock_workaround_ :: ()
haddock_workaround_ = (), name :: Value Text
name = Value Text
name,
approvalRules :: Maybe RuleGroupProperty
approvalRules = Maybe RuleGroupProperty
forall a. Maybe a
Prelude.Nothing, approvedPatches :: Maybe (ValueList Text)
approvedPatches = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesComplianceLevel = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
approvedPatchesEnableNonSecurity = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
availableSecurityUpdatesComplianceStatus = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
defaultBaseline :: Maybe (Value Bool)
defaultBaseline = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing, description :: Maybe (Value Text)
description = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
globalFilters :: Maybe PatchFilterGroupProperty
globalFilters = Maybe PatchFilterGroupProperty
forall a. Maybe a
Prelude.Nothing, operatingSystem :: Maybe (Value Text)
operatingSystem = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
patchGroups :: Maybe (ValueList Text)
patchGroups = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing, rejectedPatches :: Maybe (ValueList Text)
rejectedPatches = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
rejectedPatchesAction :: Maybe (Value Text)
rejectedPatchesAction = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, sources :: Maybe [PatchSourceProperty]
sources = Maybe [PatchSourceProperty]
forall a. Maybe a
Prelude.Nothing,
tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties PatchBaseline where
toResourceProperties :: PatchBaseline -> ResourceProperties
toResourceProperties PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::SSM::PatchBaseline", supportsTags :: Bool
supportsTags = Bool
Prelude.True,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Name" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
name]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> RuleGroupProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ApprovalRules" (RuleGroupProperty -> (Key, Value))
-> Maybe RuleGroupProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RuleGroupProperty
approvalRules,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ApprovedPatches" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
approvedPatches,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ApprovedPatchesComplianceLevel"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
approvedPatchesComplianceLevel,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ApprovedPatchesEnableNonSecurity"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
approvedPatchesEnableNonSecurity,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AvailableSecurityUpdatesComplianceStatus"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
availableSecurityUpdatesComplianceStatus,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DefaultBaseline" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
defaultBaseline,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Description" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
description,
Key -> PatchFilterGroupProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GlobalFilters" (PatchFilterGroupProperty -> (Key, Value))
-> Maybe PatchFilterGroupProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PatchFilterGroupProperty
globalFilters,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OperatingSystem" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
operatingSystem,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PatchGroups" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
patchGroups,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RejectedPatches" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
rejectedPatches,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RejectedPatchesAction"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
rejectedPatchesAction,
Key -> [PatchSourceProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Sources" ([PatchSourceProperty] -> (Key, Value))
-> Maybe [PatchSourceProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [PatchSourceProperty]
sources,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags]))}
instance JSON.ToJSON PatchBaseline where
toJSON :: PatchBaseline -> Value
toJSON PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Name" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
name]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> RuleGroupProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ApprovalRules" (RuleGroupProperty -> (Key, Value))
-> Maybe RuleGroupProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RuleGroupProperty
approvalRules,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ApprovedPatches" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
approvedPatches,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ApprovedPatchesComplianceLevel"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
approvedPatchesComplianceLevel,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ApprovedPatchesEnableNonSecurity"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
approvedPatchesEnableNonSecurity,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AvailableSecurityUpdatesComplianceStatus"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
availableSecurityUpdatesComplianceStatus,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DefaultBaseline" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
defaultBaseline,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Description" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
description,
Key -> PatchFilterGroupProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GlobalFilters" (PatchFilterGroupProperty -> (Key, Value))
-> Maybe PatchFilterGroupProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PatchFilterGroupProperty
globalFilters,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OperatingSystem" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
operatingSystem,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PatchGroups" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
patchGroups,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RejectedPatches" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
rejectedPatches,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RejectedPatchesAction"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
rejectedPatchesAction,
Key -> [PatchSourceProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Sources" ([PatchSourceProperty] -> (Key, Value))
-> Maybe [PatchSourceProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [PatchSourceProperty]
sources,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags])))
instance Property "ApprovalRules" PatchBaseline where
type PropertyType "ApprovalRules" PatchBaseline = RuleGroupProperty
set :: PropertyType "ApprovalRules" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "ApprovalRules" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {approvalRules :: Maybe RuleGroupProperty
approvalRules = RuleGroupProperty -> Maybe RuleGroupProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ApprovalRules" PatchBaseline
RuleGroupProperty
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "ApprovedPatches" PatchBaseline where
type PropertyType "ApprovedPatches" PatchBaseline = ValueList Prelude.Text
set :: PropertyType "ApprovedPatches" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "ApprovedPatches" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {approvedPatches :: Maybe (ValueList Text)
approvedPatches = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ApprovedPatches" PatchBaseline
ValueList Text
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "ApprovedPatchesComplianceLevel" PatchBaseline where
type PropertyType "ApprovedPatchesComplianceLevel" PatchBaseline = Value Prelude.Text
set :: PropertyType "ApprovedPatchesComplianceLevel" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "ApprovedPatchesComplianceLevel" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline
{approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesComplianceLevel = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ApprovedPatchesComplianceLevel" PatchBaseline
Value Text
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "ApprovedPatchesEnableNonSecurity" PatchBaseline where
type PropertyType "ApprovedPatchesEnableNonSecurity" PatchBaseline = Value Prelude.Bool
set :: PropertyType "ApprovedPatchesEnableNonSecurity" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "ApprovedPatchesEnableNonSecurity" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline
{approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
approvedPatchesEnableNonSecurity = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ApprovedPatchesEnableNonSecurity" PatchBaseline
Value Bool
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "AvailableSecurityUpdatesComplianceStatus" PatchBaseline where
type PropertyType "AvailableSecurityUpdatesComplianceStatus" PatchBaseline = Value Prelude.Text
set :: PropertyType
"AvailableSecurityUpdatesComplianceStatus" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType
"AvailableSecurityUpdatesComplianceStatus" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline
{availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
availableSecurityUpdatesComplianceStatus = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"AvailableSecurityUpdatesComplianceStatus" PatchBaseline
Value Text
newValue,
Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "DefaultBaseline" PatchBaseline where
type PropertyType "DefaultBaseline" PatchBaseline = Value Prelude.Bool
set :: PropertyType "DefaultBaseline" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "DefaultBaseline" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {defaultBaseline :: Maybe (Value Bool)
defaultBaseline = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DefaultBaseline" PatchBaseline
Value Bool
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "Description" PatchBaseline where
type PropertyType "Description" PatchBaseline = Value Prelude.Text
set :: PropertyType "Description" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "Description" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {description :: Maybe (Value Text)
description = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Description" PatchBaseline
Value Text
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "GlobalFilters" PatchBaseline where
type PropertyType "GlobalFilters" PatchBaseline = PatchFilterGroupProperty
set :: PropertyType "GlobalFilters" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "GlobalFilters" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {globalFilters :: Maybe PatchFilterGroupProperty
globalFilters = PatchFilterGroupProperty -> Maybe PatchFilterGroupProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "GlobalFilters" PatchBaseline
PatchFilterGroupProperty
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "Name" PatchBaseline where
type PropertyType "Name" PatchBaseline = Value Prelude.Text
set :: PropertyType "Name" PatchBaseline -> PatchBaseline -> PatchBaseline
set PropertyType "Name" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {name :: Value Text
name = PropertyType "Name" PatchBaseline
Value Text
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "OperatingSystem" PatchBaseline where
type PropertyType "OperatingSystem" PatchBaseline = Value Prelude.Text
set :: PropertyType "OperatingSystem" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "OperatingSystem" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {operatingSystem :: Maybe (Value Text)
operatingSystem = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "OperatingSystem" PatchBaseline
Value Text
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "PatchGroups" PatchBaseline where
type PropertyType "PatchGroups" PatchBaseline = ValueList Prelude.Text
set :: PropertyType "PatchGroups" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "PatchGroups" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {patchGroups :: Maybe (ValueList Text)
patchGroups = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PatchGroups" PatchBaseline
ValueList Text
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "RejectedPatches" PatchBaseline where
type PropertyType "RejectedPatches" PatchBaseline = ValueList Prelude.Text
set :: PropertyType "RejectedPatches" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "RejectedPatches" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {rejectedPatches :: Maybe (ValueList Text)
rejectedPatches = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RejectedPatches" PatchBaseline
ValueList Text
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "RejectedPatchesAction" PatchBaseline where
type PropertyType "RejectedPatchesAction" PatchBaseline = Value Prelude.Text
set :: PropertyType "RejectedPatchesAction" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "RejectedPatchesAction" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {rejectedPatchesAction :: Maybe (Value Text)
rejectedPatchesAction = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RejectedPatchesAction" PatchBaseline
Value Text
newValue, Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
instance Property "Sources" PatchBaseline where
type PropertyType "Sources" PatchBaseline = [PatchSourceProperty]
set :: PropertyType "Sources" PatchBaseline
-> PatchBaseline -> PatchBaseline
set PropertyType "Sources" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {sources :: Maybe [PatchSourceProperty]
sources = [PatchSourceProperty] -> Maybe [PatchSourceProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [PatchSourceProperty]
PropertyType "Sources" PatchBaseline
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
tags :: Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
instance Property "Tags" PatchBaseline where
type PropertyType "Tags" PatchBaseline = [Tag]
set :: PropertyType "Tags" PatchBaseline -> PatchBaseline -> PatchBaseline
set PropertyType "Tags" PatchBaseline
newValue PatchBaseline {Maybe [Tag]
Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: PatchBaseline -> ()
approvalRules :: PatchBaseline -> Maybe RuleGroupProperty
approvedPatches :: PatchBaseline -> Maybe (ValueList Text)
approvedPatchesComplianceLevel :: PatchBaseline -> Maybe (Value Text)
approvedPatchesEnableNonSecurity :: PatchBaseline -> Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: PatchBaseline -> Maybe (Value Text)
defaultBaseline :: PatchBaseline -> Maybe (Value Bool)
description :: PatchBaseline -> Maybe (Value Text)
globalFilters :: PatchBaseline -> Maybe PatchFilterGroupProperty
name :: PatchBaseline -> Value Text
operatingSystem :: PatchBaseline -> Maybe (Value Text)
patchGroups :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatches :: PatchBaseline -> Maybe (ValueList Text)
rejectedPatchesAction :: PatchBaseline -> Maybe (Value Text)
sources :: PatchBaseline -> Maybe [PatchSourceProperty]
tags :: PatchBaseline -> Maybe [Tag]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
tags :: Maybe [Tag]
..}
= PatchBaseline {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" PatchBaseline
newValue, Maybe [PatchSourceProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe PatchFilterGroupProperty
Maybe RuleGroupProperty
()
Value Text
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
haddock_workaround_ :: ()
approvalRules :: Maybe RuleGroupProperty
approvedPatches :: Maybe (ValueList Text)
approvedPatchesComplianceLevel :: Maybe (Value Text)
approvedPatchesEnableNonSecurity :: Maybe (Value Bool)
availableSecurityUpdatesComplianceStatus :: Maybe (Value Text)
defaultBaseline :: Maybe (Value Bool)
description :: Maybe (Value Text)
globalFilters :: Maybe PatchFilterGroupProperty
name :: Value Text
operatingSystem :: Maybe (Value Text)
patchGroups :: Maybe (ValueList Text)
rejectedPatches :: Maybe (ValueList Text)
rejectedPatchesAction :: Maybe (Value Text)
sources :: Maybe [PatchSourceProperty]
..}