module Stratosphere.RTBFabric.ResponderGateway.AutoScalingGroupsConfigurationProperty (
        AutoScalingGroupsConfigurationProperty(..),
        mkAutoScalingGroupsConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data AutoScalingGroupsConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-rtbfabric-respondergateway-autoscalinggroupsconfiguration.html>
    AutoScalingGroupsConfigurationProperty {AutoScalingGroupsConfigurationProperty -> ()
haddock_workaround_ :: (),
                                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-rtbfabric-respondergateway-autoscalinggroupsconfiguration.html#cfn-rtbfabric-respondergateway-autoscalinggroupsconfiguration-autoscalinggroupnamelist>
                                            AutoScalingGroupsConfigurationProperty -> ValueList Text
autoScalingGroupNameList :: (ValueList Prelude.Text),
                                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-rtbfabric-respondergateway-autoscalinggroupsconfiguration.html#cfn-rtbfabric-respondergateway-autoscalinggroupsconfiguration-rolearn>
                                            AutoScalingGroupsConfigurationProperty -> Value Text
roleArn :: (Value Prelude.Text)}
  deriving stock (AutoScalingGroupsConfigurationProperty
-> AutoScalingGroupsConfigurationProperty -> Bool
(AutoScalingGroupsConfigurationProperty
 -> AutoScalingGroupsConfigurationProperty -> Bool)
-> (AutoScalingGroupsConfigurationProperty
    -> AutoScalingGroupsConfigurationProperty -> Bool)
-> Eq AutoScalingGroupsConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AutoScalingGroupsConfigurationProperty
-> AutoScalingGroupsConfigurationProperty -> Bool
== :: AutoScalingGroupsConfigurationProperty
-> AutoScalingGroupsConfigurationProperty -> Bool
$c/= :: AutoScalingGroupsConfigurationProperty
-> AutoScalingGroupsConfigurationProperty -> Bool
/= :: AutoScalingGroupsConfigurationProperty
-> AutoScalingGroupsConfigurationProperty -> Bool
Prelude.Eq, Int -> AutoScalingGroupsConfigurationProperty -> ShowS
[AutoScalingGroupsConfigurationProperty] -> ShowS
AutoScalingGroupsConfigurationProperty -> String
(Int -> AutoScalingGroupsConfigurationProperty -> ShowS)
-> (AutoScalingGroupsConfigurationProperty -> String)
-> ([AutoScalingGroupsConfigurationProperty] -> ShowS)
-> Show AutoScalingGroupsConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AutoScalingGroupsConfigurationProperty -> ShowS
showsPrec :: Int -> AutoScalingGroupsConfigurationProperty -> ShowS
$cshow :: AutoScalingGroupsConfigurationProperty -> String
show :: AutoScalingGroupsConfigurationProperty -> String
$cshowList :: [AutoScalingGroupsConfigurationProperty] -> ShowS
showList :: [AutoScalingGroupsConfigurationProperty] -> ShowS
Prelude.Show)
mkAutoScalingGroupsConfigurationProperty ::
  ValueList Prelude.Text
  -> Value Prelude.Text -> AutoScalingGroupsConfigurationProperty
mkAutoScalingGroupsConfigurationProperty :: ValueList Text
-> Value Text -> AutoScalingGroupsConfigurationProperty
mkAutoScalingGroupsConfigurationProperty
  ValueList Text
autoScalingGroupNameList
  Value Text
roleArn
  = AutoScalingGroupsConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       autoScalingGroupNameList :: ValueList Text
autoScalingGroupNameList = ValueList Text
autoScalingGroupNameList,
       roleArn :: Value Text
roleArn = Value Text
roleArn}
instance ToResourceProperties AutoScalingGroupsConfigurationProperty where
  toResourceProperties :: AutoScalingGroupsConfigurationProperty -> ResourceProperties
toResourceProperties AutoScalingGroupsConfigurationProperty {()
ValueList Text
Value Text
haddock_workaround_ :: AutoScalingGroupsConfigurationProperty -> ()
autoScalingGroupNameList :: AutoScalingGroupsConfigurationProperty -> ValueList Text
roleArn :: AutoScalingGroupsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
autoScalingGroupNameList :: ValueList Text
roleArn :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::RTBFabric::ResponderGateway.AutoScalingGroupsConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"AutoScalingGroupNameList"
                         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
autoScalingGroupNameList,
                       Key
"RoleArn" 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
roleArn]}
instance JSON.ToJSON AutoScalingGroupsConfigurationProperty where
  toJSON :: AutoScalingGroupsConfigurationProperty -> Value
toJSON AutoScalingGroupsConfigurationProperty {()
ValueList Text
Value Text
haddock_workaround_ :: AutoScalingGroupsConfigurationProperty -> ()
autoScalingGroupNameList :: AutoScalingGroupsConfigurationProperty -> ValueList Text
roleArn :: AutoScalingGroupsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
autoScalingGroupNameList :: ValueList Text
roleArn :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"AutoScalingGroupNameList" 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
autoScalingGroupNameList,
         Key
"RoleArn" 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
roleArn]
instance Property "AutoScalingGroupNameList" AutoScalingGroupsConfigurationProperty where
  type PropertyType "AutoScalingGroupNameList" AutoScalingGroupsConfigurationProperty = ValueList Prelude.Text
  set :: PropertyType
  "AutoScalingGroupNameList" AutoScalingGroupsConfigurationProperty
-> AutoScalingGroupsConfigurationProperty
-> AutoScalingGroupsConfigurationProperty
set PropertyType
  "AutoScalingGroupNameList" AutoScalingGroupsConfigurationProperty
newValue AutoScalingGroupsConfigurationProperty {()
ValueList Text
Value Text
haddock_workaround_ :: AutoScalingGroupsConfigurationProperty -> ()
autoScalingGroupNameList :: AutoScalingGroupsConfigurationProperty -> ValueList Text
roleArn :: AutoScalingGroupsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
autoScalingGroupNameList :: ValueList Text
roleArn :: Value Text
..}
    = AutoScalingGroupsConfigurationProperty
        {autoScalingGroupNameList :: ValueList Text
autoScalingGroupNameList = PropertyType
  "AutoScalingGroupNameList" AutoScalingGroupsConfigurationProperty
ValueList Text
newValue, ()
Value Text
haddock_workaround_ :: ()
roleArn :: Value Text
haddock_workaround_ :: ()
roleArn :: Value Text
..}
instance Property "RoleArn" AutoScalingGroupsConfigurationProperty where
  type PropertyType "RoleArn" AutoScalingGroupsConfigurationProperty = Value Prelude.Text
  set :: PropertyType "RoleArn" AutoScalingGroupsConfigurationProperty
-> AutoScalingGroupsConfigurationProperty
-> AutoScalingGroupsConfigurationProperty
set PropertyType "RoleArn" AutoScalingGroupsConfigurationProperty
newValue AutoScalingGroupsConfigurationProperty {()
ValueList Text
Value Text
haddock_workaround_ :: AutoScalingGroupsConfigurationProperty -> ()
autoScalingGroupNameList :: AutoScalingGroupsConfigurationProperty -> ValueList Text
roleArn :: AutoScalingGroupsConfigurationProperty -> Value Text
haddock_workaround_ :: ()
autoScalingGroupNameList :: ValueList Text
roleArn :: Value Text
..}
    = AutoScalingGroupsConfigurationProperty {roleArn :: Value Text
roleArn = PropertyType "RoleArn" AutoScalingGroupsConfigurationProperty
Value Text
newValue, ()
ValueList Text
haddock_workaround_ :: ()
autoScalingGroupNameList :: ValueList Text
haddock_workaround_ :: ()
autoScalingGroupNameList :: ValueList Text
..}