module Stratosphere.PCS.ComputeNodeGroup.ScalingConfigurationProperty (
ScalingConfigurationProperty(..), mkScalingConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ScalingConfigurationProperty
=
ScalingConfigurationProperty {ScalingConfigurationProperty -> ()
haddock_workaround_ :: (),
ScalingConfigurationProperty -> Value Integer
maxInstanceCount :: (Value Prelude.Integer),
ScalingConfigurationProperty -> Value Integer
minInstanceCount :: (Value Prelude.Integer)}
deriving stock (ScalingConfigurationProperty
-> ScalingConfigurationProperty -> Bool
(ScalingConfigurationProperty
-> ScalingConfigurationProperty -> Bool)
-> (ScalingConfigurationProperty
-> ScalingConfigurationProperty -> Bool)
-> Eq ScalingConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScalingConfigurationProperty
-> ScalingConfigurationProperty -> Bool
== :: ScalingConfigurationProperty
-> ScalingConfigurationProperty -> Bool
$c/= :: ScalingConfigurationProperty
-> ScalingConfigurationProperty -> Bool
/= :: ScalingConfigurationProperty
-> ScalingConfigurationProperty -> Bool
Prelude.Eq, Int -> ScalingConfigurationProperty -> ShowS
[ScalingConfigurationProperty] -> ShowS
ScalingConfigurationProperty -> String
(Int -> ScalingConfigurationProperty -> ShowS)
-> (ScalingConfigurationProperty -> String)
-> ([ScalingConfigurationProperty] -> ShowS)
-> Show ScalingConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScalingConfigurationProperty -> ShowS
showsPrec :: Int -> ScalingConfigurationProperty -> ShowS
$cshow :: ScalingConfigurationProperty -> String
show :: ScalingConfigurationProperty -> String
$cshowList :: [ScalingConfigurationProperty] -> ShowS
showList :: [ScalingConfigurationProperty] -> ShowS
Prelude.Show)
mkScalingConfigurationProperty ::
Value Prelude.Integer
-> Value Prelude.Integer -> ScalingConfigurationProperty
mkScalingConfigurationProperty :: Value Integer -> Value Integer -> ScalingConfigurationProperty
mkScalingConfigurationProperty Value Integer
maxInstanceCount Value Integer
minInstanceCount
= ScalingConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), maxInstanceCount :: Value Integer
maxInstanceCount = Value Integer
maxInstanceCount,
minInstanceCount :: Value Integer
minInstanceCount = Value Integer
minInstanceCount}
instance ToResourceProperties ScalingConfigurationProperty where
toResourceProperties :: ScalingConfigurationProperty -> ResourceProperties
toResourceProperties ScalingConfigurationProperty {()
Value Integer
haddock_workaround_ :: ScalingConfigurationProperty -> ()
maxInstanceCount :: ScalingConfigurationProperty -> Value Integer
minInstanceCount :: ScalingConfigurationProperty -> Value Integer
haddock_workaround_ :: ()
maxInstanceCount :: Value Integer
minInstanceCount :: Value Integer
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::PCS::ComputeNodeGroup.ScalingConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"MaxInstanceCount" 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..= Value Integer
maxInstanceCount,
Key
"MinInstanceCount" 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..= Value Integer
minInstanceCount]}
instance JSON.ToJSON ScalingConfigurationProperty where
toJSON :: ScalingConfigurationProperty -> Value
toJSON ScalingConfigurationProperty {()
Value Integer
haddock_workaround_ :: ScalingConfigurationProperty -> ()
maxInstanceCount :: ScalingConfigurationProperty -> Value Integer
minInstanceCount :: ScalingConfigurationProperty -> Value Integer
haddock_workaround_ :: ()
maxInstanceCount :: Value Integer
minInstanceCount :: Value Integer
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"MaxInstanceCount" 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..= Value Integer
maxInstanceCount,
Key
"MinInstanceCount" 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..= Value Integer
minInstanceCount]
instance Property "MaxInstanceCount" ScalingConfigurationProperty where
type PropertyType "MaxInstanceCount" ScalingConfigurationProperty = Value Prelude.Integer
set :: PropertyType "MaxInstanceCount" ScalingConfigurationProperty
-> ScalingConfigurationProperty -> ScalingConfigurationProperty
set PropertyType "MaxInstanceCount" ScalingConfigurationProperty
newValue ScalingConfigurationProperty {()
Value Integer
haddock_workaround_ :: ScalingConfigurationProperty -> ()
maxInstanceCount :: ScalingConfigurationProperty -> Value Integer
minInstanceCount :: ScalingConfigurationProperty -> Value Integer
haddock_workaround_ :: ()
maxInstanceCount :: Value Integer
minInstanceCount :: Value Integer
..}
= ScalingConfigurationProperty {maxInstanceCount :: Value Integer
maxInstanceCount = PropertyType "MaxInstanceCount" ScalingConfigurationProperty
Value Integer
newValue, ()
Value Integer
haddock_workaround_ :: ()
minInstanceCount :: Value Integer
haddock_workaround_ :: ()
minInstanceCount :: Value Integer
..}
instance Property "MinInstanceCount" ScalingConfigurationProperty where
type PropertyType "MinInstanceCount" ScalingConfigurationProperty = Value Prelude.Integer
set :: PropertyType "MinInstanceCount" ScalingConfigurationProperty
-> ScalingConfigurationProperty -> ScalingConfigurationProperty
set PropertyType "MinInstanceCount" ScalingConfigurationProperty
newValue ScalingConfigurationProperty {()
Value Integer
haddock_workaround_ :: ScalingConfigurationProperty -> ()
maxInstanceCount :: ScalingConfigurationProperty -> Value Integer
minInstanceCount :: ScalingConfigurationProperty -> Value Integer
haddock_workaround_ :: ()
maxInstanceCount :: Value Integer
minInstanceCount :: Value Integer
..}
= ScalingConfigurationProperty {minInstanceCount :: Value Integer
minInstanceCount = PropertyType "MinInstanceCount" ScalingConfigurationProperty
Value Integer
newValue, ()
Value Integer
haddock_workaround_ :: ()
maxInstanceCount :: Value Integer
haddock_workaround_ :: ()
maxInstanceCount :: Value Integer
..}