module Stratosphere.SSM.Association (
module Exports, Association(..), mkAssociation
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.SSM.Association.InstanceAssociationOutputLocationProperty as Exports
import {-# SOURCE #-} Stratosphere.SSM.Association.TargetProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data Association
=
Association {Association -> ()
haddock_workaround_ :: (),
Association -> Maybe (Value Bool)
applyOnlyAtCronInterval :: (Prelude.Maybe (Value Prelude.Bool)),
Association -> Maybe (Value Text)
associationName :: (Prelude.Maybe (Value Prelude.Text)),
Association -> Maybe (Value Text)
automationTargetParameterName :: (Prelude.Maybe (Value Prelude.Text)),
Association -> Maybe (ValueList Text)
calendarNames :: (Prelude.Maybe (ValueList Prelude.Text)),
Association -> Maybe (Value Text)
complianceSeverity :: (Prelude.Maybe (Value Prelude.Text)),
Association -> Maybe (Value Text)
documentVersion :: (Prelude.Maybe (Value Prelude.Text)),
Association -> Maybe (Value Text)
instanceId :: (Prelude.Maybe (Value Prelude.Text)),
Association -> Maybe (Value Text)
maxConcurrency :: (Prelude.Maybe (Value Prelude.Text)),
Association -> Maybe (Value Text)
maxErrors :: (Prelude.Maybe (Value Prelude.Text)),
Association -> Value Text
name :: (Value Prelude.Text),
Association -> Maybe InstanceAssociationOutputLocationProperty
outputLocation :: (Prelude.Maybe InstanceAssociationOutputLocationProperty),
Association -> Maybe Object
parameters :: (Prelude.Maybe JSON.Object),
Association -> Maybe (Value Text)
scheduleExpression :: (Prelude.Maybe (Value Prelude.Text)),
Association -> Maybe (Value Integer)
scheduleOffset :: (Prelude.Maybe (Value Prelude.Integer)),
Association -> Maybe (Value Text)
syncCompliance :: (Prelude.Maybe (Value Prelude.Text)),
Association -> Maybe [TargetProperty]
targets :: (Prelude.Maybe [TargetProperty]),
Association -> Maybe (Value Integer)
waitForSuccessTimeoutSeconds :: (Prelude.Maybe (Value Prelude.Integer))}
deriving stock (Association -> Association -> Bool
(Association -> Association -> Bool)
-> (Association -> Association -> Bool) -> Eq Association
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Association -> Association -> Bool
== :: Association -> Association -> Bool
$c/= :: Association -> Association -> Bool
/= :: Association -> Association -> Bool
Prelude.Eq, Int -> Association -> ShowS
[Association] -> ShowS
Association -> String
(Int -> Association -> ShowS)
-> (Association -> String)
-> ([Association] -> ShowS)
-> Show Association
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Association -> ShowS
showsPrec :: Int -> Association -> ShowS
$cshow :: Association -> String
show :: Association -> String
$cshowList :: [Association] -> ShowS
showList :: [Association] -> ShowS
Prelude.Show)
mkAssociation :: Value Prelude.Text -> Association
mkAssociation :: Value Text -> Association
mkAssociation Value Text
name
= Association
{haddock_workaround_ :: ()
haddock_workaround_ = (), name :: Value Text
name = Value Text
name,
applyOnlyAtCronInterval :: Maybe (Value Bool)
applyOnlyAtCronInterval = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
associationName :: Maybe (Value Text)
associationName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
automationTargetParameterName :: Maybe (Value Text)
automationTargetParameterName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
calendarNames :: Maybe (ValueList Text)
calendarNames = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
complianceSeverity :: Maybe (Value Text)
complianceSeverity = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
documentVersion :: Maybe (Value Text)
documentVersion = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, instanceId :: Maybe (Value Text)
instanceId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
maxConcurrency :: Maybe (Value Text)
maxConcurrency = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, maxErrors :: Maybe (Value Text)
maxErrors = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
outputLocation = Maybe InstanceAssociationOutputLocationProperty
forall a. Maybe a
Prelude.Nothing, parameters :: Maybe Object
parameters = Maybe Object
forall a. Maybe a
Prelude.Nothing,
scheduleExpression :: Maybe (Value Text)
scheduleExpression = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
scheduleOffset :: Maybe (Value Integer)
scheduleOffset = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, syncCompliance :: Maybe (Value Text)
syncCompliance = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
targets :: Maybe [TargetProperty]
targets = Maybe [TargetProperty]
forall a. Maybe a
Prelude.Nothing,
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
waitForSuccessTimeoutSeconds = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties Association where
toResourceProperties :: Association -> ResourceProperties
toResourceProperties Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::SSM::Association", supportsTags :: Bool
supportsTags = Bool
Prelude.False,
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 -> 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
"ApplyOnlyAtCronInterval"
(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)
applyOnlyAtCronInterval,
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
"AssociationName" (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)
associationName,
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
"AutomationTargetParameterName"
(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)
automationTargetParameterName,
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
"CalendarNames" (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)
calendarNames,
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
"ComplianceSeverity" (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)
complianceSeverity,
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
"DocumentVersion" (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)
documentVersion,
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
"InstanceId" (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)
instanceId,
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
"MaxConcurrency" (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)
maxConcurrency,
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
"MaxErrors" (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)
maxErrors,
Key -> InstanceAssociationOutputLocationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OutputLocation" (InstanceAssociationOutputLocationProperty -> (Key, Value))
-> Maybe InstanceAssociationOutputLocationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InstanceAssociationOutputLocationProperty
outputLocation,
Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Parameters" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
parameters,
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
"ScheduleExpression" (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)
scheduleExpression,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ScheduleOffset" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
scheduleOffset,
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
"SyncCompliance" (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)
syncCompliance,
Key -> [TargetProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Targets" ([TargetProperty] -> (Key, Value))
-> Maybe [TargetProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TargetProperty]
targets,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WaitForSuccessTimeoutSeconds"
(Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
waitForSuccessTimeoutSeconds]))}
instance JSON.ToJSON Association where
toJSON :: Association -> Value
toJSON Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= [(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 -> 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
"ApplyOnlyAtCronInterval"
(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)
applyOnlyAtCronInterval,
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
"AssociationName" (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)
associationName,
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
"AutomationTargetParameterName"
(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)
automationTargetParameterName,
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
"CalendarNames" (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)
calendarNames,
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
"ComplianceSeverity" (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)
complianceSeverity,
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
"DocumentVersion" (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)
documentVersion,
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
"InstanceId" (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)
instanceId,
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
"MaxConcurrency" (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)
maxConcurrency,
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
"MaxErrors" (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)
maxErrors,
Key -> InstanceAssociationOutputLocationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"OutputLocation" (InstanceAssociationOutputLocationProperty -> (Key, Value))
-> Maybe InstanceAssociationOutputLocationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InstanceAssociationOutputLocationProperty
outputLocation,
Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Parameters" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
parameters,
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
"ScheduleExpression" (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)
scheduleExpression,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ScheduleOffset" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
scheduleOffset,
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
"SyncCompliance" (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)
syncCompliance,
Key -> [TargetProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Targets" ([TargetProperty] -> (Key, Value))
-> Maybe [TargetProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TargetProperty]
targets,
Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WaitForSuccessTimeoutSeconds"
(Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
waitForSuccessTimeoutSeconds])))
instance Property "ApplyOnlyAtCronInterval" Association where
type PropertyType "ApplyOnlyAtCronInterval" Association = Value Prelude.Bool
set :: PropertyType "ApplyOnlyAtCronInterval" Association
-> Association -> Association
set PropertyType "ApplyOnlyAtCronInterval" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {applyOnlyAtCronInterval :: Maybe (Value Bool)
applyOnlyAtCronInterval = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ApplyOnlyAtCronInterval" Association
Value Bool
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "AssociationName" Association where
type PropertyType "AssociationName" Association = Value Prelude.Text
set :: PropertyType "AssociationName" Association
-> Association -> Association
set PropertyType "AssociationName" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {associationName :: Maybe (Value Text)
associationName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AssociationName" Association
Value Text
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "AutomationTargetParameterName" Association where
type PropertyType "AutomationTargetParameterName" Association = Value Prelude.Text
set :: PropertyType "AutomationTargetParameterName" Association
-> Association -> Association
set PropertyType "AutomationTargetParameterName" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association
{automationTargetParameterName :: Maybe (Value Text)
automationTargetParameterName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AutomationTargetParameterName" Association
Value Text
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "CalendarNames" Association where
type PropertyType "CalendarNames" Association = ValueList Prelude.Text
set :: PropertyType "CalendarNames" Association
-> Association -> Association
set PropertyType "CalendarNames" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {calendarNames :: Maybe (ValueList Text)
calendarNames = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CalendarNames" Association
ValueList Text
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "ComplianceSeverity" Association where
type PropertyType "ComplianceSeverity" Association = Value Prelude.Text
set :: PropertyType "ComplianceSeverity" Association
-> Association -> Association
set PropertyType "ComplianceSeverity" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {complianceSeverity :: Maybe (Value Text)
complianceSeverity = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ComplianceSeverity" Association
Value Text
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "DocumentVersion" Association where
type PropertyType "DocumentVersion" Association = Value Prelude.Text
set :: PropertyType "DocumentVersion" Association
-> Association -> Association
set PropertyType "DocumentVersion" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {documentVersion :: Maybe (Value Text)
documentVersion = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DocumentVersion" Association
Value Text
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "InstanceId" Association where
type PropertyType "InstanceId" Association = Value Prelude.Text
set :: PropertyType "InstanceId" Association -> Association -> Association
set PropertyType "InstanceId" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {instanceId :: Maybe (Value Text)
instanceId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InstanceId" Association
Value Text
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "MaxConcurrency" Association where
type PropertyType "MaxConcurrency" Association = Value Prelude.Text
set :: PropertyType "MaxConcurrency" Association
-> Association -> Association
set PropertyType "MaxConcurrency" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {maxConcurrency :: Maybe (Value Text)
maxConcurrency = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MaxConcurrency" Association
Value Text
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "MaxErrors" Association where
type PropertyType "MaxErrors" Association = Value Prelude.Text
set :: PropertyType "MaxErrors" Association -> Association -> Association
set PropertyType "MaxErrors" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {maxErrors :: Maybe (Value Text)
maxErrors = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MaxErrors" Association
Value Text
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "Name" Association where
type PropertyType "Name" Association = Value Prelude.Text
set :: PropertyType "Name" Association -> Association -> Association
set PropertyType "Name" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..} = Association {name :: Value Text
name = PropertyType "Name" Association
Value Text
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "OutputLocation" Association where
type PropertyType "OutputLocation" Association = InstanceAssociationOutputLocationProperty
set :: PropertyType "OutputLocation" Association
-> Association -> Association
set PropertyType "OutputLocation" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {outputLocation :: Maybe InstanceAssociationOutputLocationProperty
outputLocation = InstanceAssociationOutputLocationProperty
-> Maybe InstanceAssociationOutputLocationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "OutputLocation" Association
InstanceAssociationOutputLocationProperty
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "Parameters" Association where
type PropertyType "Parameters" Association = JSON.Object
set :: PropertyType "Parameters" Association -> Association -> Association
set PropertyType "Parameters" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {parameters :: Maybe Object
parameters = Object -> Maybe Object
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure Object
PropertyType "Parameters" Association
newValue, Maybe [TargetProperty]
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "ScheduleExpression" Association where
type PropertyType "ScheduleExpression" Association = Value Prelude.Text
set :: PropertyType "ScheduleExpression" Association
-> Association -> Association
set PropertyType "ScheduleExpression" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {scheduleExpression :: Maybe (Value Text)
scheduleExpression = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ScheduleExpression" Association
Value Text
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "ScheduleOffset" Association where
type PropertyType "ScheduleOffset" Association = Value Prelude.Integer
set :: PropertyType "ScheduleOffset" Association
-> Association -> Association
set PropertyType "ScheduleOffset" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {scheduleOffset :: Maybe (Value Integer)
scheduleOffset = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ScheduleOffset" Association
Value Integer
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "SyncCompliance" Association where
type PropertyType "SyncCompliance" Association = Value Prelude.Text
set :: PropertyType "SyncCompliance" Association
-> Association -> Association
set PropertyType "SyncCompliance" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {syncCompliance :: Maybe (Value Text)
syncCompliance = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SyncCompliance" Association
Value Text
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "Targets" Association where
type PropertyType "Targets" Association = [TargetProperty]
set :: PropertyType "Targets" Association -> Association -> Association
set PropertyType "Targets" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association {targets :: Maybe [TargetProperty]
targets = [TargetProperty] -> Maybe [TargetProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [TargetProperty]
PropertyType "Targets" Association
newValue, Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
instance Property "WaitForSuccessTimeoutSeconds" Association where
type PropertyType "WaitForSuccessTimeoutSeconds" Association = Value Prelude.Integer
set :: PropertyType "WaitForSuccessTimeoutSeconds" Association
-> Association -> Association
set PropertyType "WaitForSuccessTimeoutSeconds" Association
newValue Association {Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: Association -> ()
applyOnlyAtCronInterval :: Association -> Maybe (Value Bool)
associationName :: Association -> Maybe (Value Text)
automationTargetParameterName :: Association -> Maybe (Value Text)
calendarNames :: Association -> Maybe (ValueList Text)
complianceSeverity :: Association -> Maybe (Value Text)
documentVersion :: Association -> Maybe (Value Text)
instanceId :: Association -> Maybe (Value Text)
maxConcurrency :: Association -> Maybe (Value Text)
maxErrors :: Association -> Maybe (Value Text)
name :: Association -> Value Text
outputLocation :: Association -> Maybe InstanceAssociationOutputLocationProperty
parameters :: Association -> Maybe Object
scheduleExpression :: Association -> Maybe (Value Text)
scheduleOffset :: Association -> Maybe (Value Integer)
syncCompliance :: Association -> Maybe (Value Text)
targets :: Association -> Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Association -> Maybe (Value Integer)
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
..}
= Association
{waitForSuccessTimeoutSeconds :: Maybe (Value Integer)
waitForSuccessTimeoutSeconds = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "WaitForSuccessTimeoutSeconds" Association
Value Integer
newValue, Maybe [TargetProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
Maybe InstanceAssociationOutputLocationProperty
()
Value Text
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
haddock_workaround_ :: ()
applyOnlyAtCronInterval :: Maybe (Value Bool)
associationName :: Maybe (Value Text)
automationTargetParameterName :: Maybe (Value Text)
calendarNames :: Maybe (ValueList Text)
complianceSeverity :: Maybe (Value Text)
documentVersion :: Maybe (Value Text)
instanceId :: Maybe (Value Text)
maxConcurrency :: Maybe (Value Text)
maxErrors :: Maybe (Value Text)
name :: Value Text
outputLocation :: Maybe InstanceAssociationOutputLocationProperty
parameters :: Maybe Object
scheduleExpression :: Maybe (Value Text)
scheduleOffset :: Maybe (Value Integer)
syncCompliance :: Maybe (Value Text)
targets :: Maybe [TargetProperty]
..}