{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.SSM.UpdateAssociation
(
UpdateAssociation (..),
newUpdateAssociation,
updateAssociation_alarmConfiguration,
updateAssociation_applyOnlyAtCronInterval,
updateAssociation_associationName,
updateAssociation_associationVersion,
updateAssociation_automationTargetParameterName,
updateAssociation_calendarNames,
updateAssociation_complianceSeverity,
updateAssociation_documentVersion,
updateAssociation_maxConcurrency,
updateAssociation_maxErrors,
updateAssociation_name,
updateAssociation_outputLocation,
updateAssociation_parameters,
updateAssociation_scheduleExpression,
updateAssociation_scheduleOffset,
updateAssociation_syncCompliance,
updateAssociation_targetLocations,
updateAssociation_targetMaps,
updateAssociation_targets,
updateAssociation_associationId,
UpdateAssociationResponse (..),
newUpdateAssociationResponse,
updateAssociationResponse_associationDescription,
updateAssociationResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SSM.Types
data UpdateAssociation = UpdateAssociation'
{ UpdateAssociation -> Maybe AlarmConfiguration
alarmConfiguration :: Prelude.Maybe AlarmConfiguration,
UpdateAssociation -> Maybe Bool
applyOnlyAtCronInterval :: Prelude.Maybe Prelude.Bool,
UpdateAssociation -> Maybe Text
associationName :: Prelude.Maybe Prelude.Text,
UpdateAssociation -> Maybe Text
associationVersion :: Prelude.Maybe Prelude.Text,
UpdateAssociation -> Maybe Text
automationTargetParameterName :: Prelude.Maybe Prelude.Text,
UpdateAssociation -> Maybe [Text]
calendarNames :: Prelude.Maybe [Prelude.Text],
UpdateAssociation -> Maybe AssociationComplianceSeverity
complianceSeverity :: Prelude.Maybe AssociationComplianceSeverity,
UpdateAssociation -> Maybe Text
documentVersion :: Prelude.Maybe Prelude.Text,
UpdateAssociation -> Maybe Text
maxConcurrency :: Prelude.Maybe Prelude.Text,
UpdateAssociation -> Maybe Text
maxErrors :: Prelude.Maybe Prelude.Text,
UpdateAssociation -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
UpdateAssociation -> Maybe InstanceAssociationOutputLocation
outputLocation :: Prelude.Maybe InstanceAssociationOutputLocation,
UpdateAssociation -> Maybe (Sensitive (HashMap Text [Text]))
parameters :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text [Prelude.Text])),
UpdateAssociation -> Maybe Text
scheduleExpression :: Prelude.Maybe Prelude.Text,
UpdateAssociation -> Maybe Natural
scheduleOffset :: Prelude.Maybe Prelude.Natural,
UpdateAssociation -> Maybe AssociationSyncCompliance
syncCompliance :: Prelude.Maybe AssociationSyncCompliance,
UpdateAssociation -> Maybe (NonEmpty TargetLocation)
targetLocations :: Prelude.Maybe (Prelude.NonEmpty TargetLocation),
UpdateAssociation -> Maybe [HashMap Text [Text]]
targetMaps :: Prelude.Maybe [Prelude.HashMap Prelude.Text [Prelude.Text]],
UpdateAssociation -> Maybe [Target]
targets :: Prelude.Maybe [Target],
UpdateAssociation -> Text
associationId :: Prelude.Text
}
deriving (UpdateAssociation -> UpdateAssociation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateAssociation -> UpdateAssociation -> Bool
$c/= :: UpdateAssociation -> UpdateAssociation -> Bool
== :: UpdateAssociation -> UpdateAssociation -> Bool
$c== :: UpdateAssociation -> UpdateAssociation -> Bool
Prelude.Eq, Int -> UpdateAssociation -> ShowS
[UpdateAssociation] -> ShowS
UpdateAssociation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateAssociation] -> ShowS
$cshowList :: [UpdateAssociation] -> ShowS
show :: UpdateAssociation -> String
$cshow :: UpdateAssociation -> String
showsPrec :: Int -> UpdateAssociation -> ShowS
$cshowsPrec :: Int -> UpdateAssociation -> ShowS
Prelude.Show, forall x. Rep UpdateAssociation x -> UpdateAssociation
forall x. UpdateAssociation -> Rep UpdateAssociation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateAssociation x -> UpdateAssociation
$cfrom :: forall x. UpdateAssociation -> Rep UpdateAssociation x
Prelude.Generic)
newUpdateAssociation ::
Prelude.Text ->
UpdateAssociation
newUpdateAssociation :: Text -> UpdateAssociation
newUpdateAssociation Text
pAssociationId_ =
UpdateAssociation'
{ $sel:alarmConfiguration:UpdateAssociation' :: Maybe AlarmConfiguration
alarmConfiguration =
forall a. Maybe a
Prelude.Nothing,
$sel:applyOnlyAtCronInterval:UpdateAssociation' :: Maybe Bool
applyOnlyAtCronInterval = forall a. Maybe a
Prelude.Nothing,
$sel:associationName:UpdateAssociation' :: Maybe Text
associationName = forall a. Maybe a
Prelude.Nothing,
$sel:associationVersion:UpdateAssociation' :: Maybe Text
associationVersion = forall a. Maybe a
Prelude.Nothing,
$sel:automationTargetParameterName:UpdateAssociation' :: Maybe Text
automationTargetParameterName = forall a. Maybe a
Prelude.Nothing,
$sel:calendarNames:UpdateAssociation' :: Maybe [Text]
calendarNames = forall a. Maybe a
Prelude.Nothing,
$sel:complianceSeverity:UpdateAssociation' :: Maybe AssociationComplianceSeverity
complianceSeverity = forall a. Maybe a
Prelude.Nothing,
$sel:documentVersion:UpdateAssociation' :: Maybe Text
documentVersion = forall a. Maybe a
Prelude.Nothing,
$sel:maxConcurrency:UpdateAssociation' :: Maybe Text
maxConcurrency = forall a. Maybe a
Prelude.Nothing,
$sel:maxErrors:UpdateAssociation' :: Maybe Text
maxErrors = forall a. Maybe a
Prelude.Nothing,
$sel:name:UpdateAssociation' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
$sel:outputLocation:UpdateAssociation' :: Maybe InstanceAssociationOutputLocation
outputLocation = forall a. Maybe a
Prelude.Nothing,
$sel:parameters:UpdateAssociation' :: Maybe (Sensitive (HashMap Text [Text]))
parameters = forall a. Maybe a
Prelude.Nothing,
$sel:scheduleExpression:UpdateAssociation' :: Maybe Text
scheduleExpression = forall a. Maybe a
Prelude.Nothing,
$sel:scheduleOffset:UpdateAssociation' :: Maybe Natural
scheduleOffset = forall a. Maybe a
Prelude.Nothing,
$sel:syncCompliance:UpdateAssociation' :: Maybe AssociationSyncCompliance
syncCompliance = forall a. Maybe a
Prelude.Nothing,
$sel:targetLocations:UpdateAssociation' :: Maybe (NonEmpty TargetLocation)
targetLocations = forall a. Maybe a
Prelude.Nothing,
$sel:targetMaps:UpdateAssociation' :: Maybe [HashMap Text [Text]]
targetMaps = forall a. Maybe a
Prelude.Nothing,
$sel:targets:UpdateAssociation' :: Maybe [Target]
targets = forall a. Maybe a
Prelude.Nothing,
$sel:associationId:UpdateAssociation' :: Text
associationId = Text
pAssociationId_
}
updateAssociation_alarmConfiguration :: Lens.Lens' UpdateAssociation (Prelude.Maybe AlarmConfiguration)
updateAssociation_alarmConfiguration :: Lens' UpdateAssociation (Maybe AlarmConfiguration)
updateAssociation_alarmConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe AlarmConfiguration
alarmConfiguration :: Maybe AlarmConfiguration
$sel:alarmConfiguration:UpdateAssociation' :: UpdateAssociation -> Maybe AlarmConfiguration
alarmConfiguration} -> Maybe AlarmConfiguration
alarmConfiguration) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe AlarmConfiguration
a -> UpdateAssociation
s {$sel:alarmConfiguration:UpdateAssociation' :: Maybe AlarmConfiguration
alarmConfiguration = Maybe AlarmConfiguration
a} :: UpdateAssociation)
updateAssociation_applyOnlyAtCronInterval :: Lens.Lens' UpdateAssociation (Prelude.Maybe Prelude.Bool)
updateAssociation_applyOnlyAtCronInterval :: Lens' UpdateAssociation (Maybe Bool)
updateAssociation_applyOnlyAtCronInterval = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe Bool
applyOnlyAtCronInterval :: Maybe Bool
$sel:applyOnlyAtCronInterval:UpdateAssociation' :: UpdateAssociation -> Maybe Bool
applyOnlyAtCronInterval} -> Maybe Bool
applyOnlyAtCronInterval) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe Bool
a -> UpdateAssociation
s {$sel:applyOnlyAtCronInterval:UpdateAssociation' :: Maybe Bool
applyOnlyAtCronInterval = Maybe Bool
a} :: UpdateAssociation)
updateAssociation_associationName :: Lens.Lens' UpdateAssociation (Prelude.Maybe Prelude.Text)
updateAssociation_associationName :: Lens' UpdateAssociation (Maybe Text)
updateAssociation_associationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe Text
associationName :: Maybe Text
$sel:associationName:UpdateAssociation' :: UpdateAssociation -> Maybe Text
associationName} -> Maybe Text
associationName) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe Text
a -> UpdateAssociation
s {$sel:associationName:UpdateAssociation' :: Maybe Text
associationName = Maybe Text
a} :: UpdateAssociation)
updateAssociation_associationVersion :: Lens.Lens' UpdateAssociation (Prelude.Maybe Prelude.Text)
updateAssociation_associationVersion :: Lens' UpdateAssociation (Maybe Text)
updateAssociation_associationVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe Text
associationVersion :: Maybe Text
$sel:associationVersion:UpdateAssociation' :: UpdateAssociation -> Maybe Text
associationVersion} -> Maybe Text
associationVersion) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe Text
a -> UpdateAssociation
s {$sel:associationVersion:UpdateAssociation' :: Maybe Text
associationVersion = Maybe Text
a} :: UpdateAssociation)
updateAssociation_automationTargetParameterName :: Lens.Lens' UpdateAssociation (Prelude.Maybe Prelude.Text)
updateAssociation_automationTargetParameterName :: Lens' UpdateAssociation (Maybe Text)
updateAssociation_automationTargetParameterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe Text
automationTargetParameterName :: Maybe Text
$sel:automationTargetParameterName:UpdateAssociation' :: UpdateAssociation -> Maybe Text
automationTargetParameterName} -> Maybe Text
automationTargetParameterName) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe Text
a -> UpdateAssociation
s {$sel:automationTargetParameterName:UpdateAssociation' :: Maybe Text
automationTargetParameterName = Maybe Text
a} :: UpdateAssociation)
updateAssociation_calendarNames :: Lens.Lens' UpdateAssociation (Prelude.Maybe [Prelude.Text])
updateAssociation_calendarNames :: Lens' UpdateAssociation (Maybe [Text])
updateAssociation_calendarNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe [Text]
calendarNames :: Maybe [Text]
$sel:calendarNames:UpdateAssociation' :: UpdateAssociation -> Maybe [Text]
calendarNames} -> Maybe [Text]
calendarNames) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe [Text]
a -> UpdateAssociation
s {$sel:calendarNames:UpdateAssociation' :: Maybe [Text]
calendarNames = Maybe [Text]
a} :: UpdateAssociation) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
updateAssociation_complianceSeverity :: Lens.Lens' UpdateAssociation (Prelude.Maybe AssociationComplianceSeverity)
updateAssociation_complianceSeverity :: Lens' UpdateAssociation (Maybe AssociationComplianceSeverity)
updateAssociation_complianceSeverity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe AssociationComplianceSeverity
complianceSeverity :: Maybe AssociationComplianceSeverity
$sel:complianceSeverity:UpdateAssociation' :: UpdateAssociation -> Maybe AssociationComplianceSeverity
complianceSeverity} -> Maybe AssociationComplianceSeverity
complianceSeverity) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe AssociationComplianceSeverity
a -> UpdateAssociation
s {$sel:complianceSeverity:UpdateAssociation' :: Maybe AssociationComplianceSeverity
complianceSeverity = Maybe AssociationComplianceSeverity
a} :: UpdateAssociation)
updateAssociation_documentVersion :: Lens.Lens' UpdateAssociation (Prelude.Maybe Prelude.Text)
updateAssociation_documentVersion :: Lens' UpdateAssociation (Maybe Text)
updateAssociation_documentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe Text
documentVersion :: Maybe Text
$sel:documentVersion:UpdateAssociation' :: UpdateAssociation -> Maybe Text
documentVersion} -> Maybe Text
documentVersion) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe Text
a -> UpdateAssociation
s {$sel:documentVersion:UpdateAssociation' :: Maybe Text
documentVersion = Maybe Text
a} :: UpdateAssociation)
updateAssociation_maxConcurrency :: Lens.Lens' UpdateAssociation (Prelude.Maybe Prelude.Text)
updateAssociation_maxConcurrency :: Lens' UpdateAssociation (Maybe Text)
updateAssociation_maxConcurrency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe Text
maxConcurrency :: Maybe Text
$sel:maxConcurrency:UpdateAssociation' :: UpdateAssociation -> Maybe Text
maxConcurrency} -> Maybe Text
maxConcurrency) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe Text
a -> UpdateAssociation
s {$sel:maxConcurrency:UpdateAssociation' :: Maybe Text
maxConcurrency = Maybe Text
a} :: UpdateAssociation)
updateAssociation_maxErrors :: Lens.Lens' UpdateAssociation (Prelude.Maybe Prelude.Text)
updateAssociation_maxErrors :: Lens' UpdateAssociation (Maybe Text)
updateAssociation_maxErrors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe Text
maxErrors :: Maybe Text
$sel:maxErrors:UpdateAssociation' :: UpdateAssociation -> Maybe Text
maxErrors} -> Maybe Text
maxErrors) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe Text
a -> UpdateAssociation
s {$sel:maxErrors:UpdateAssociation' :: Maybe Text
maxErrors = Maybe Text
a} :: UpdateAssociation)
updateAssociation_name :: Lens.Lens' UpdateAssociation (Prelude.Maybe Prelude.Text)
updateAssociation_name :: Lens' UpdateAssociation (Maybe Text)
updateAssociation_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe Text
name :: Maybe Text
$sel:name:UpdateAssociation' :: UpdateAssociation -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe Text
a -> UpdateAssociation
s {$sel:name:UpdateAssociation' :: Maybe Text
name = Maybe Text
a} :: UpdateAssociation)
updateAssociation_outputLocation :: Lens.Lens' UpdateAssociation (Prelude.Maybe InstanceAssociationOutputLocation)
updateAssociation_outputLocation :: Lens' UpdateAssociation (Maybe InstanceAssociationOutputLocation)
updateAssociation_outputLocation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe InstanceAssociationOutputLocation
outputLocation :: Maybe InstanceAssociationOutputLocation
$sel:outputLocation:UpdateAssociation' :: UpdateAssociation -> Maybe InstanceAssociationOutputLocation
outputLocation} -> Maybe InstanceAssociationOutputLocation
outputLocation) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe InstanceAssociationOutputLocation
a -> UpdateAssociation
s {$sel:outputLocation:UpdateAssociation' :: Maybe InstanceAssociationOutputLocation
outputLocation = Maybe InstanceAssociationOutputLocation
a} :: UpdateAssociation)
updateAssociation_parameters :: Lens.Lens' UpdateAssociation (Prelude.Maybe (Prelude.HashMap Prelude.Text [Prelude.Text]))
updateAssociation_parameters :: Lens' UpdateAssociation (Maybe (HashMap Text [Text]))
updateAssociation_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe (Sensitive (HashMap Text [Text]))
parameters :: Maybe (Sensitive (HashMap Text [Text]))
$sel:parameters:UpdateAssociation' :: UpdateAssociation -> Maybe (Sensitive (HashMap Text [Text]))
parameters} -> Maybe (Sensitive (HashMap Text [Text]))
parameters) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe (Sensitive (HashMap Text [Text]))
a -> UpdateAssociation
s {$sel:parameters:UpdateAssociation' :: Maybe (Sensitive (HashMap Text [Text]))
parameters = Maybe (Sensitive (HashMap Text [Text]))
a} :: UpdateAssociation) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping (forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)
updateAssociation_scheduleExpression :: Lens.Lens' UpdateAssociation (Prelude.Maybe Prelude.Text)
updateAssociation_scheduleExpression :: Lens' UpdateAssociation (Maybe Text)
updateAssociation_scheduleExpression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe Text
scheduleExpression :: Maybe Text
$sel:scheduleExpression:UpdateAssociation' :: UpdateAssociation -> Maybe Text
scheduleExpression} -> Maybe Text
scheduleExpression) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe Text
a -> UpdateAssociation
s {$sel:scheduleExpression:UpdateAssociation' :: Maybe Text
scheduleExpression = Maybe Text
a} :: UpdateAssociation)
updateAssociation_scheduleOffset :: Lens.Lens' UpdateAssociation (Prelude.Maybe Prelude.Natural)
updateAssociation_scheduleOffset :: Lens' UpdateAssociation (Maybe Natural)
updateAssociation_scheduleOffset = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe Natural
scheduleOffset :: Maybe Natural
$sel:scheduleOffset:UpdateAssociation' :: UpdateAssociation -> Maybe Natural
scheduleOffset} -> Maybe Natural
scheduleOffset) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe Natural
a -> UpdateAssociation
s {$sel:scheduleOffset:UpdateAssociation' :: Maybe Natural
scheduleOffset = Maybe Natural
a} :: UpdateAssociation)
updateAssociation_syncCompliance :: Lens.Lens' UpdateAssociation (Prelude.Maybe AssociationSyncCompliance)
updateAssociation_syncCompliance :: Lens' UpdateAssociation (Maybe AssociationSyncCompliance)
updateAssociation_syncCompliance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe AssociationSyncCompliance
syncCompliance :: Maybe AssociationSyncCompliance
$sel:syncCompliance:UpdateAssociation' :: UpdateAssociation -> Maybe AssociationSyncCompliance
syncCompliance} -> Maybe AssociationSyncCompliance
syncCompliance) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe AssociationSyncCompliance
a -> UpdateAssociation
s {$sel:syncCompliance:UpdateAssociation' :: Maybe AssociationSyncCompliance
syncCompliance = Maybe AssociationSyncCompliance
a} :: UpdateAssociation)
updateAssociation_targetLocations :: Lens.Lens' UpdateAssociation (Prelude.Maybe (Prelude.NonEmpty TargetLocation))
updateAssociation_targetLocations :: Lens' UpdateAssociation (Maybe (NonEmpty TargetLocation))
updateAssociation_targetLocations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe (NonEmpty TargetLocation)
targetLocations :: Maybe (NonEmpty TargetLocation)
$sel:targetLocations:UpdateAssociation' :: UpdateAssociation -> Maybe (NonEmpty TargetLocation)
targetLocations} -> Maybe (NonEmpty TargetLocation)
targetLocations) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe (NonEmpty TargetLocation)
a -> UpdateAssociation
s {$sel:targetLocations:UpdateAssociation' :: Maybe (NonEmpty TargetLocation)
targetLocations = Maybe (NonEmpty TargetLocation)
a} :: UpdateAssociation) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
updateAssociation_targetMaps :: Lens.Lens' UpdateAssociation (Prelude.Maybe [Prelude.HashMap Prelude.Text [Prelude.Text]])
updateAssociation_targetMaps :: Lens' UpdateAssociation (Maybe [HashMap Text [Text]])
updateAssociation_targetMaps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe [HashMap Text [Text]]
targetMaps :: Maybe [HashMap Text [Text]]
$sel:targetMaps:UpdateAssociation' :: UpdateAssociation -> Maybe [HashMap Text [Text]]
targetMaps} -> Maybe [HashMap Text [Text]]
targetMaps) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe [HashMap Text [Text]]
a -> UpdateAssociation
s {$sel:targetMaps:UpdateAssociation' :: Maybe [HashMap Text [Text]]
targetMaps = Maybe [HashMap Text [Text]]
a} :: UpdateAssociation) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
updateAssociation_targets :: Lens.Lens' UpdateAssociation (Prelude.Maybe [Target])
updateAssociation_targets :: Lens' UpdateAssociation (Maybe [Target])
updateAssociation_targets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Maybe [Target]
targets :: Maybe [Target]
$sel:targets:UpdateAssociation' :: UpdateAssociation -> Maybe [Target]
targets} -> Maybe [Target]
targets) (\s :: UpdateAssociation
s@UpdateAssociation' {} Maybe [Target]
a -> UpdateAssociation
s {$sel:targets:UpdateAssociation' :: Maybe [Target]
targets = Maybe [Target]
a} :: UpdateAssociation) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
updateAssociation_associationId :: Lens.Lens' UpdateAssociation Prelude.Text
updateAssociation_associationId :: Lens' UpdateAssociation Text
updateAssociation_associationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociation' {Text
associationId :: Text
$sel:associationId:UpdateAssociation' :: UpdateAssociation -> Text
associationId} -> Text
associationId) (\s :: UpdateAssociation
s@UpdateAssociation' {} Text
a -> UpdateAssociation
s {$sel:associationId:UpdateAssociation' :: Text
associationId = Text
a} :: UpdateAssociation)
instance Core.AWSRequest UpdateAssociation where
type
AWSResponse UpdateAssociation =
UpdateAssociationResponse
request :: (Service -> Service)
-> UpdateAssociation -> Request UpdateAssociation
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateAssociation
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse UpdateAssociation)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
( \Int
s ResponseHeaders
h Object
x ->
Maybe AssociationDescription -> Int -> UpdateAssociationResponse
UpdateAssociationResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"AssociationDescription")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
)
instance Prelude.Hashable UpdateAssociation where
hashWithSalt :: Int -> UpdateAssociation -> Int
hashWithSalt Int
_salt UpdateAssociation' {Maybe Bool
Maybe Natural
Maybe [Text]
Maybe [HashMap Text [Text]]
Maybe [Target]
Maybe (NonEmpty TargetLocation)
Maybe Text
Maybe (Sensitive (HashMap Text [Text]))
Maybe AlarmConfiguration
Maybe AssociationComplianceSeverity
Maybe AssociationSyncCompliance
Maybe InstanceAssociationOutputLocation
Text
associationId :: Text
targets :: Maybe [Target]
targetMaps :: Maybe [HashMap Text [Text]]
targetLocations :: Maybe (NonEmpty TargetLocation)
syncCompliance :: Maybe AssociationSyncCompliance
scheduleOffset :: Maybe Natural
scheduleExpression :: Maybe Text
parameters :: Maybe (Sensitive (HashMap Text [Text]))
outputLocation :: Maybe InstanceAssociationOutputLocation
name :: Maybe Text
maxErrors :: Maybe Text
maxConcurrency :: Maybe Text
documentVersion :: Maybe Text
complianceSeverity :: Maybe AssociationComplianceSeverity
calendarNames :: Maybe [Text]
automationTargetParameterName :: Maybe Text
associationVersion :: Maybe Text
associationName :: Maybe Text
applyOnlyAtCronInterval :: Maybe Bool
alarmConfiguration :: Maybe AlarmConfiguration
$sel:associationId:UpdateAssociation' :: UpdateAssociation -> Text
$sel:targets:UpdateAssociation' :: UpdateAssociation -> Maybe [Target]
$sel:targetMaps:UpdateAssociation' :: UpdateAssociation -> Maybe [HashMap Text [Text]]
$sel:targetLocations:UpdateAssociation' :: UpdateAssociation -> Maybe (NonEmpty TargetLocation)
$sel:syncCompliance:UpdateAssociation' :: UpdateAssociation -> Maybe AssociationSyncCompliance
$sel:scheduleOffset:UpdateAssociation' :: UpdateAssociation -> Maybe Natural
$sel:scheduleExpression:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:parameters:UpdateAssociation' :: UpdateAssociation -> Maybe (Sensitive (HashMap Text [Text]))
$sel:outputLocation:UpdateAssociation' :: UpdateAssociation -> Maybe InstanceAssociationOutputLocation
$sel:name:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:maxErrors:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:maxConcurrency:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:documentVersion:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:complianceSeverity:UpdateAssociation' :: UpdateAssociation -> Maybe AssociationComplianceSeverity
$sel:calendarNames:UpdateAssociation' :: UpdateAssociation -> Maybe [Text]
$sel:automationTargetParameterName:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:associationVersion:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:associationName:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:applyOnlyAtCronInterval:UpdateAssociation' :: UpdateAssociation -> Maybe Bool
$sel:alarmConfiguration:UpdateAssociation' :: UpdateAssociation -> Maybe AlarmConfiguration
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AlarmConfiguration
alarmConfiguration
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
applyOnlyAtCronInterval
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
associationName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
associationVersion
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
automationTargetParameterName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
calendarNames
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AssociationComplianceSeverity
complianceSeverity
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
documentVersion
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxConcurrency
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxErrors
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InstanceAssociationOutputLocation
outputLocation
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive (HashMap Text [Text]))
parameters
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
scheduleExpression
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
scheduleOffset
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AssociationSyncCompliance
syncCompliance
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty TargetLocation)
targetLocations
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [HashMap Text [Text]]
targetMaps
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Target]
targets
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
associationId
instance Prelude.NFData UpdateAssociation where
rnf :: UpdateAssociation -> ()
rnf UpdateAssociation' {Maybe Bool
Maybe Natural
Maybe [Text]
Maybe [HashMap Text [Text]]
Maybe [Target]
Maybe (NonEmpty TargetLocation)
Maybe Text
Maybe (Sensitive (HashMap Text [Text]))
Maybe AlarmConfiguration
Maybe AssociationComplianceSeverity
Maybe AssociationSyncCompliance
Maybe InstanceAssociationOutputLocation
Text
associationId :: Text
targets :: Maybe [Target]
targetMaps :: Maybe [HashMap Text [Text]]
targetLocations :: Maybe (NonEmpty TargetLocation)
syncCompliance :: Maybe AssociationSyncCompliance
scheduleOffset :: Maybe Natural
scheduleExpression :: Maybe Text
parameters :: Maybe (Sensitive (HashMap Text [Text]))
outputLocation :: Maybe InstanceAssociationOutputLocation
name :: Maybe Text
maxErrors :: Maybe Text
maxConcurrency :: Maybe Text
documentVersion :: Maybe Text
complianceSeverity :: Maybe AssociationComplianceSeverity
calendarNames :: Maybe [Text]
automationTargetParameterName :: Maybe Text
associationVersion :: Maybe Text
associationName :: Maybe Text
applyOnlyAtCronInterval :: Maybe Bool
alarmConfiguration :: Maybe AlarmConfiguration
$sel:associationId:UpdateAssociation' :: UpdateAssociation -> Text
$sel:targets:UpdateAssociation' :: UpdateAssociation -> Maybe [Target]
$sel:targetMaps:UpdateAssociation' :: UpdateAssociation -> Maybe [HashMap Text [Text]]
$sel:targetLocations:UpdateAssociation' :: UpdateAssociation -> Maybe (NonEmpty TargetLocation)
$sel:syncCompliance:UpdateAssociation' :: UpdateAssociation -> Maybe AssociationSyncCompliance
$sel:scheduleOffset:UpdateAssociation' :: UpdateAssociation -> Maybe Natural
$sel:scheduleExpression:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:parameters:UpdateAssociation' :: UpdateAssociation -> Maybe (Sensitive (HashMap Text [Text]))
$sel:outputLocation:UpdateAssociation' :: UpdateAssociation -> Maybe InstanceAssociationOutputLocation
$sel:name:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:maxErrors:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:maxConcurrency:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:documentVersion:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:complianceSeverity:UpdateAssociation' :: UpdateAssociation -> Maybe AssociationComplianceSeverity
$sel:calendarNames:UpdateAssociation' :: UpdateAssociation -> Maybe [Text]
$sel:automationTargetParameterName:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:associationVersion:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:associationName:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:applyOnlyAtCronInterval:UpdateAssociation' :: UpdateAssociation -> Maybe Bool
$sel:alarmConfiguration:UpdateAssociation' :: UpdateAssociation -> Maybe AlarmConfiguration
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe AlarmConfiguration
alarmConfiguration
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
applyOnlyAtCronInterval
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
associationName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
associationVersion
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
automationTargetParameterName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
calendarNames
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AssociationComplianceSeverity
complianceSeverity
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
documentVersion
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxConcurrency
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxErrors
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceAssociationOutputLocation
outputLocation
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text [Text]))
parameters
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
scheduleExpression
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
scheduleOffset
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AssociationSyncCompliance
syncCompliance
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty TargetLocation)
targetLocations
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [HashMap Text [Text]]
targetMaps
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Target]
targets
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
associationId
instance Data.ToHeaders UpdateAssociation where
toHeaders :: UpdateAssociation -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AmazonSSM.UpdateAssociation" ::
Prelude.ByteString
),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON UpdateAssociation where
toJSON :: UpdateAssociation -> Value
toJSON UpdateAssociation' {Maybe Bool
Maybe Natural
Maybe [Text]
Maybe [HashMap Text [Text]]
Maybe [Target]
Maybe (NonEmpty TargetLocation)
Maybe Text
Maybe (Sensitive (HashMap Text [Text]))
Maybe AlarmConfiguration
Maybe AssociationComplianceSeverity
Maybe AssociationSyncCompliance
Maybe InstanceAssociationOutputLocation
Text
associationId :: Text
targets :: Maybe [Target]
targetMaps :: Maybe [HashMap Text [Text]]
targetLocations :: Maybe (NonEmpty TargetLocation)
syncCompliance :: Maybe AssociationSyncCompliance
scheduleOffset :: Maybe Natural
scheduleExpression :: Maybe Text
parameters :: Maybe (Sensitive (HashMap Text [Text]))
outputLocation :: Maybe InstanceAssociationOutputLocation
name :: Maybe Text
maxErrors :: Maybe Text
maxConcurrency :: Maybe Text
documentVersion :: Maybe Text
complianceSeverity :: Maybe AssociationComplianceSeverity
calendarNames :: Maybe [Text]
automationTargetParameterName :: Maybe Text
associationVersion :: Maybe Text
associationName :: Maybe Text
applyOnlyAtCronInterval :: Maybe Bool
alarmConfiguration :: Maybe AlarmConfiguration
$sel:associationId:UpdateAssociation' :: UpdateAssociation -> Text
$sel:targets:UpdateAssociation' :: UpdateAssociation -> Maybe [Target]
$sel:targetMaps:UpdateAssociation' :: UpdateAssociation -> Maybe [HashMap Text [Text]]
$sel:targetLocations:UpdateAssociation' :: UpdateAssociation -> Maybe (NonEmpty TargetLocation)
$sel:syncCompliance:UpdateAssociation' :: UpdateAssociation -> Maybe AssociationSyncCompliance
$sel:scheduleOffset:UpdateAssociation' :: UpdateAssociation -> Maybe Natural
$sel:scheduleExpression:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:parameters:UpdateAssociation' :: UpdateAssociation -> Maybe (Sensitive (HashMap Text [Text]))
$sel:outputLocation:UpdateAssociation' :: UpdateAssociation -> Maybe InstanceAssociationOutputLocation
$sel:name:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:maxErrors:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:maxConcurrency:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:documentVersion:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:complianceSeverity:UpdateAssociation' :: UpdateAssociation -> Maybe AssociationComplianceSeverity
$sel:calendarNames:UpdateAssociation' :: UpdateAssociation -> Maybe [Text]
$sel:automationTargetParameterName:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:associationVersion:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:associationName:UpdateAssociation' :: UpdateAssociation -> Maybe Text
$sel:applyOnlyAtCronInterval:UpdateAssociation' :: UpdateAssociation -> Maybe Bool
$sel:alarmConfiguration:UpdateAssociation' :: UpdateAssociation -> Maybe AlarmConfiguration
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"AlarmConfiguration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AlarmConfiguration
alarmConfiguration,
(Key
"ApplyOnlyAtCronInterval" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
applyOnlyAtCronInterval,
(Key
"AssociationName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
associationName,
(Key
"AssociationVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
associationVersion,
(Key
"AutomationTargetParameterName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
automationTargetParameterName,
(Key
"CalendarNames" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
calendarNames,
(Key
"ComplianceSeverity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AssociationComplianceSeverity
complianceSeverity,
(Key
"DocumentVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
documentVersion,
(Key
"MaxConcurrency" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
maxConcurrency,
(Key
"MaxErrors" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
maxErrors,
(Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
name,
(Key
"OutputLocation" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InstanceAssociationOutputLocation
outputLocation,
(Key
"Parameters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive (HashMap Text [Text]))
parameters,
(Key
"ScheduleExpression" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
scheduleExpression,
(Key
"ScheduleOffset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
scheduleOffset,
(Key
"SyncCompliance" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AssociationSyncCompliance
syncCompliance,
(Key
"TargetLocations" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty TargetLocation)
targetLocations,
(Key
"TargetMaps" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [HashMap Text [Text]]
targetMaps,
(Key
"Targets" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Target]
targets,
forall a. a -> Maybe a
Prelude.Just
(Key
"AssociationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
associationId)
]
)
instance Data.ToPath UpdateAssociation where
toPath :: UpdateAssociation -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery UpdateAssociation where
toQuery :: UpdateAssociation -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data UpdateAssociationResponse = UpdateAssociationResponse'
{
UpdateAssociationResponse -> Maybe AssociationDescription
associationDescription :: Prelude.Maybe AssociationDescription,
UpdateAssociationResponse -> Int
httpStatus :: Prelude.Int
}
deriving (UpdateAssociationResponse -> UpdateAssociationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateAssociationResponse -> UpdateAssociationResponse -> Bool
$c/= :: UpdateAssociationResponse -> UpdateAssociationResponse -> Bool
== :: UpdateAssociationResponse -> UpdateAssociationResponse -> Bool
$c== :: UpdateAssociationResponse -> UpdateAssociationResponse -> Bool
Prelude.Eq, Int -> UpdateAssociationResponse -> ShowS
[UpdateAssociationResponse] -> ShowS
UpdateAssociationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateAssociationResponse] -> ShowS
$cshowList :: [UpdateAssociationResponse] -> ShowS
show :: UpdateAssociationResponse -> String
$cshow :: UpdateAssociationResponse -> String
showsPrec :: Int -> UpdateAssociationResponse -> ShowS
$cshowsPrec :: Int -> UpdateAssociationResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateAssociationResponse x -> UpdateAssociationResponse
forall x.
UpdateAssociationResponse -> Rep UpdateAssociationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateAssociationResponse x -> UpdateAssociationResponse
$cfrom :: forall x.
UpdateAssociationResponse -> Rep UpdateAssociationResponse x
Prelude.Generic)
newUpdateAssociationResponse ::
Prelude.Int ->
UpdateAssociationResponse
newUpdateAssociationResponse :: Int -> UpdateAssociationResponse
newUpdateAssociationResponse Int
pHttpStatus_ =
UpdateAssociationResponse'
{ $sel:associationDescription:UpdateAssociationResponse' :: Maybe AssociationDescription
associationDescription =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:UpdateAssociationResponse' :: Int
httpStatus = Int
pHttpStatus_
}
updateAssociationResponse_associationDescription :: Lens.Lens' UpdateAssociationResponse (Prelude.Maybe AssociationDescription)
updateAssociationResponse_associationDescription :: Lens' UpdateAssociationResponse (Maybe AssociationDescription)
updateAssociationResponse_associationDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociationResponse' {Maybe AssociationDescription
associationDescription :: Maybe AssociationDescription
$sel:associationDescription:UpdateAssociationResponse' :: UpdateAssociationResponse -> Maybe AssociationDescription
associationDescription} -> Maybe AssociationDescription
associationDescription) (\s :: UpdateAssociationResponse
s@UpdateAssociationResponse' {} Maybe AssociationDescription
a -> UpdateAssociationResponse
s {$sel:associationDescription:UpdateAssociationResponse' :: Maybe AssociationDescription
associationDescription = Maybe AssociationDescription
a} :: UpdateAssociationResponse)
updateAssociationResponse_httpStatus :: Lens.Lens' UpdateAssociationResponse Prelude.Int
updateAssociationResponse_httpStatus :: Lens' UpdateAssociationResponse Int
updateAssociationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAssociationResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateAssociationResponse' :: UpdateAssociationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateAssociationResponse
s@UpdateAssociationResponse' {} Int
a -> UpdateAssociationResponse
s {$sel:httpStatus:UpdateAssociationResponse' :: Int
httpStatus = Int
a} :: UpdateAssociationResponse)
instance Prelude.NFData UpdateAssociationResponse where
rnf :: UpdateAssociationResponse -> ()
rnf UpdateAssociationResponse' {Int
Maybe AssociationDescription
httpStatus :: Int
associationDescription :: Maybe AssociationDescription
$sel:httpStatus:UpdateAssociationResponse' :: UpdateAssociationResponse -> Int
$sel:associationDescription:UpdateAssociationResponse' :: UpdateAssociationResponse -> Maybe AssociationDescription
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe AssociationDescription
associationDescription
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus