module Stratosphere.Budgets.BudgetsAction.SsmActionDefinitionProperty (
SsmActionDefinitionProperty(..), mkSsmActionDefinitionProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data SsmActionDefinitionProperty
=
SsmActionDefinitionProperty {SsmActionDefinitionProperty -> ()
haddock_workaround_ :: (),
SsmActionDefinitionProperty -> ValueList Text
instanceIds :: (ValueList Prelude.Text),
SsmActionDefinitionProperty -> Value Text
region :: (Value Prelude.Text),
SsmActionDefinitionProperty -> Value Text
subtype :: (Value Prelude.Text)}
deriving stock (SsmActionDefinitionProperty -> SsmActionDefinitionProperty -> Bool
(SsmActionDefinitionProperty
-> SsmActionDefinitionProperty -> Bool)
-> (SsmActionDefinitionProperty
-> SsmActionDefinitionProperty -> Bool)
-> Eq SsmActionDefinitionProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SsmActionDefinitionProperty -> SsmActionDefinitionProperty -> Bool
== :: SsmActionDefinitionProperty -> SsmActionDefinitionProperty -> Bool
$c/= :: SsmActionDefinitionProperty -> SsmActionDefinitionProperty -> Bool
/= :: SsmActionDefinitionProperty -> SsmActionDefinitionProperty -> Bool
Prelude.Eq, Int -> SsmActionDefinitionProperty -> ShowS
[SsmActionDefinitionProperty] -> ShowS
SsmActionDefinitionProperty -> String
(Int -> SsmActionDefinitionProperty -> ShowS)
-> (SsmActionDefinitionProperty -> String)
-> ([SsmActionDefinitionProperty] -> ShowS)
-> Show SsmActionDefinitionProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SsmActionDefinitionProperty -> ShowS
showsPrec :: Int -> SsmActionDefinitionProperty -> ShowS
$cshow :: SsmActionDefinitionProperty -> String
show :: SsmActionDefinitionProperty -> String
$cshowList :: [SsmActionDefinitionProperty] -> ShowS
showList :: [SsmActionDefinitionProperty] -> ShowS
Prelude.Show)
mkSsmActionDefinitionProperty ::
ValueList Prelude.Text
-> Value Prelude.Text
-> Value Prelude.Text -> SsmActionDefinitionProperty
mkSsmActionDefinitionProperty :: ValueList Text
-> Value Text -> Value Text -> SsmActionDefinitionProperty
mkSsmActionDefinitionProperty ValueList Text
instanceIds Value Text
region Value Text
subtype
= SsmActionDefinitionProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), instanceIds :: ValueList Text
instanceIds = ValueList Text
instanceIds,
region :: Value Text
region = Value Text
region, subtype :: Value Text
subtype = Value Text
subtype}
instance ToResourceProperties SsmActionDefinitionProperty where
toResourceProperties :: SsmActionDefinitionProperty -> ResourceProperties
toResourceProperties SsmActionDefinitionProperty {()
ValueList Text
Value Text
haddock_workaround_ :: SsmActionDefinitionProperty -> ()
instanceIds :: SsmActionDefinitionProperty -> ValueList Text
region :: SsmActionDefinitionProperty -> Value Text
subtype :: SsmActionDefinitionProperty -> Value Text
haddock_workaround_ :: ()
instanceIds :: ValueList Text
region :: Value Text
subtype :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Budgets::BudgetsAction.SsmActionDefinition",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"InstanceIds" 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..= ValueList Text
instanceIds,
Key
"Region" 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
region, Key
"Subtype" 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
subtype]}
instance JSON.ToJSON SsmActionDefinitionProperty where
toJSON :: SsmActionDefinitionProperty -> Value
toJSON SsmActionDefinitionProperty {()
ValueList Text
Value Text
haddock_workaround_ :: SsmActionDefinitionProperty -> ()
instanceIds :: SsmActionDefinitionProperty -> ValueList Text
region :: SsmActionDefinitionProperty -> Value Text
subtype :: SsmActionDefinitionProperty -> Value Text
haddock_workaround_ :: ()
instanceIds :: ValueList Text
region :: Value Text
subtype :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"InstanceIds" 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..= ValueList Text
instanceIds, Key
"Region" 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
region,
Key
"Subtype" 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
subtype]
instance Property "InstanceIds" SsmActionDefinitionProperty where
type PropertyType "InstanceIds" SsmActionDefinitionProperty = ValueList Prelude.Text
set :: PropertyType "InstanceIds" SsmActionDefinitionProperty
-> SsmActionDefinitionProperty -> SsmActionDefinitionProperty
set PropertyType "InstanceIds" SsmActionDefinitionProperty
newValue SsmActionDefinitionProperty {()
ValueList Text
Value Text
haddock_workaround_ :: SsmActionDefinitionProperty -> ()
instanceIds :: SsmActionDefinitionProperty -> ValueList Text
region :: SsmActionDefinitionProperty -> Value Text
subtype :: SsmActionDefinitionProperty -> Value Text
haddock_workaround_ :: ()
instanceIds :: ValueList Text
region :: Value Text
subtype :: Value Text
..}
= SsmActionDefinitionProperty {instanceIds :: ValueList Text
instanceIds = PropertyType "InstanceIds" SsmActionDefinitionProperty
ValueList Text
newValue, ()
Value Text
haddock_workaround_ :: ()
region :: Value Text
subtype :: Value Text
haddock_workaround_ :: ()
region :: Value Text
subtype :: Value Text
..}
instance Property "Region" SsmActionDefinitionProperty where
type PropertyType "Region" SsmActionDefinitionProperty = Value Prelude.Text
set :: PropertyType "Region" SsmActionDefinitionProperty
-> SsmActionDefinitionProperty -> SsmActionDefinitionProperty
set PropertyType "Region" SsmActionDefinitionProperty
newValue SsmActionDefinitionProperty {()
ValueList Text
Value Text
haddock_workaround_ :: SsmActionDefinitionProperty -> ()
instanceIds :: SsmActionDefinitionProperty -> ValueList Text
region :: SsmActionDefinitionProperty -> Value Text
subtype :: SsmActionDefinitionProperty -> Value Text
haddock_workaround_ :: ()
instanceIds :: ValueList Text
region :: Value Text
subtype :: Value Text
..}
= SsmActionDefinitionProperty {region :: Value Text
region = PropertyType "Region" SsmActionDefinitionProperty
Value Text
newValue, ()
ValueList Text
Value Text
haddock_workaround_ :: ()
instanceIds :: ValueList Text
subtype :: Value Text
haddock_workaround_ :: ()
instanceIds :: ValueList Text
subtype :: Value Text
..}
instance Property "Subtype" SsmActionDefinitionProperty where
type PropertyType "Subtype" SsmActionDefinitionProperty = Value Prelude.Text
set :: PropertyType "Subtype" SsmActionDefinitionProperty
-> SsmActionDefinitionProperty -> SsmActionDefinitionProperty
set PropertyType "Subtype" SsmActionDefinitionProperty
newValue SsmActionDefinitionProperty {()
ValueList Text
Value Text
haddock_workaround_ :: SsmActionDefinitionProperty -> ()
instanceIds :: SsmActionDefinitionProperty -> ValueList Text
region :: SsmActionDefinitionProperty -> Value Text
subtype :: SsmActionDefinitionProperty -> Value Text
haddock_workaround_ :: ()
instanceIds :: ValueList Text
region :: Value Text
subtype :: Value Text
..}
= SsmActionDefinitionProperty {subtype :: Value Text
subtype = PropertyType "Subtype" SsmActionDefinitionProperty
Value Text
newValue, ()
ValueList Text
Value Text
haddock_workaround_ :: ()
instanceIds :: ValueList Text
region :: Value Text
haddock_workaround_ :: ()
instanceIds :: ValueList Text
region :: Value Text
..}