module Stratosphere.DocDB.DBCluster.ServerlessV2ScalingConfigurationProperty (
ServerlessV2ScalingConfigurationProperty(..),
mkServerlessV2ScalingConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ServerlessV2ScalingConfigurationProperty
=
ServerlessV2ScalingConfigurationProperty {ServerlessV2ScalingConfigurationProperty -> ()
haddock_workaround_ :: (),
ServerlessV2ScalingConfigurationProperty -> Value Double
maxCapacity :: (Value Prelude.Double),
ServerlessV2ScalingConfigurationProperty -> Value Double
minCapacity :: (Value Prelude.Double)}
deriving stock (ServerlessV2ScalingConfigurationProperty
-> ServerlessV2ScalingConfigurationProperty -> Bool
(ServerlessV2ScalingConfigurationProperty
-> ServerlessV2ScalingConfigurationProperty -> Bool)
-> (ServerlessV2ScalingConfigurationProperty
-> ServerlessV2ScalingConfigurationProperty -> Bool)
-> Eq ServerlessV2ScalingConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ServerlessV2ScalingConfigurationProperty
-> ServerlessV2ScalingConfigurationProperty -> Bool
== :: ServerlessV2ScalingConfigurationProperty
-> ServerlessV2ScalingConfigurationProperty -> Bool
$c/= :: ServerlessV2ScalingConfigurationProperty
-> ServerlessV2ScalingConfigurationProperty -> Bool
/= :: ServerlessV2ScalingConfigurationProperty
-> ServerlessV2ScalingConfigurationProperty -> Bool
Prelude.Eq, Int -> ServerlessV2ScalingConfigurationProperty -> ShowS
[ServerlessV2ScalingConfigurationProperty] -> ShowS
ServerlessV2ScalingConfigurationProperty -> String
(Int -> ServerlessV2ScalingConfigurationProperty -> ShowS)
-> (ServerlessV2ScalingConfigurationProperty -> String)
-> ([ServerlessV2ScalingConfigurationProperty] -> ShowS)
-> Show ServerlessV2ScalingConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ServerlessV2ScalingConfigurationProperty -> ShowS
showsPrec :: Int -> ServerlessV2ScalingConfigurationProperty -> ShowS
$cshow :: ServerlessV2ScalingConfigurationProperty -> String
show :: ServerlessV2ScalingConfigurationProperty -> String
$cshowList :: [ServerlessV2ScalingConfigurationProperty] -> ShowS
showList :: [ServerlessV2ScalingConfigurationProperty] -> ShowS
Prelude.Show)
mkServerlessV2ScalingConfigurationProperty ::
Value Prelude.Double
-> Value Prelude.Double -> ServerlessV2ScalingConfigurationProperty
mkServerlessV2ScalingConfigurationProperty :: Value Double
-> Value Double -> ServerlessV2ScalingConfigurationProperty
mkServerlessV2ScalingConfigurationProperty Value Double
maxCapacity Value Double
minCapacity
= ServerlessV2ScalingConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), maxCapacity :: Value Double
maxCapacity = Value Double
maxCapacity,
minCapacity :: Value Double
minCapacity = Value Double
minCapacity}
instance ToResourceProperties ServerlessV2ScalingConfigurationProperty where
toResourceProperties :: ServerlessV2ScalingConfigurationProperty -> ResourceProperties
toResourceProperties ServerlessV2ScalingConfigurationProperty {()
Value Double
haddock_workaround_ :: ServerlessV2ScalingConfigurationProperty -> ()
maxCapacity :: ServerlessV2ScalingConfigurationProperty -> Value Double
minCapacity :: ServerlessV2ScalingConfigurationProperty -> Value Double
haddock_workaround_ :: ()
maxCapacity :: Value Double
minCapacity :: Value Double
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::DocDB::DBCluster.ServerlessV2ScalingConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"MaxCapacity" Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Double
maxCapacity,
Key
"MinCapacity" Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Double
minCapacity]}
instance JSON.ToJSON ServerlessV2ScalingConfigurationProperty where
toJSON :: ServerlessV2ScalingConfigurationProperty -> Value
toJSON ServerlessV2ScalingConfigurationProperty {()
Value Double
haddock_workaround_ :: ServerlessV2ScalingConfigurationProperty -> ()
maxCapacity :: ServerlessV2ScalingConfigurationProperty -> Value Double
minCapacity :: ServerlessV2ScalingConfigurationProperty -> Value Double
haddock_workaround_ :: ()
maxCapacity :: Value Double
minCapacity :: Value Double
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"MaxCapacity" Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Double
maxCapacity,
Key
"MinCapacity" Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Double
minCapacity]
instance Property "MaxCapacity" ServerlessV2ScalingConfigurationProperty where
type PropertyType "MaxCapacity" ServerlessV2ScalingConfigurationProperty = Value Prelude.Double
set :: PropertyType "MaxCapacity" ServerlessV2ScalingConfigurationProperty
-> ServerlessV2ScalingConfigurationProperty
-> ServerlessV2ScalingConfigurationProperty
set PropertyType "MaxCapacity" ServerlessV2ScalingConfigurationProperty
newValue ServerlessV2ScalingConfigurationProperty {()
Value Double
haddock_workaround_ :: ServerlessV2ScalingConfigurationProperty -> ()
maxCapacity :: ServerlessV2ScalingConfigurationProperty -> Value Double
minCapacity :: ServerlessV2ScalingConfigurationProperty -> Value Double
haddock_workaround_ :: ()
maxCapacity :: Value Double
minCapacity :: Value Double
..}
= ServerlessV2ScalingConfigurationProperty
{maxCapacity :: Value Double
maxCapacity = PropertyType "MaxCapacity" ServerlessV2ScalingConfigurationProperty
Value Double
newValue, ()
Value Double
haddock_workaround_ :: ()
minCapacity :: Value Double
haddock_workaround_ :: ()
minCapacity :: Value Double
..}
instance Property "MinCapacity" ServerlessV2ScalingConfigurationProperty where
type PropertyType "MinCapacity" ServerlessV2ScalingConfigurationProperty = Value Prelude.Double
set :: PropertyType "MinCapacity" ServerlessV2ScalingConfigurationProperty
-> ServerlessV2ScalingConfigurationProperty
-> ServerlessV2ScalingConfigurationProperty
set PropertyType "MinCapacity" ServerlessV2ScalingConfigurationProperty
newValue ServerlessV2ScalingConfigurationProperty {()
Value Double
haddock_workaround_ :: ServerlessV2ScalingConfigurationProperty -> ()
maxCapacity :: ServerlessV2ScalingConfigurationProperty -> Value Double
minCapacity :: ServerlessV2ScalingConfigurationProperty -> Value Double
haddock_workaround_ :: ()
maxCapacity :: Value Double
minCapacity :: Value Double
..}
= ServerlessV2ScalingConfigurationProperty
{minCapacity :: Value Double
minCapacity = PropertyType "MinCapacity" ServerlessV2ScalingConfigurationProperty
Value Double
newValue, ()
Value Double
haddock_workaround_ :: ()
maxCapacity :: Value Double
haddock_workaround_ :: ()
maxCapacity :: Value Double
..}