module Stratosphere.RDS.DBCluster.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 -> Maybe (Value Bool)
autoPause :: (Prelude.Maybe (Value Prelude.Bool)),
ScalingConfigurationProperty -> Maybe (Value Integer)
maxCapacity :: (Prelude.Maybe (Value Prelude.Integer)),
ScalingConfigurationProperty -> Maybe (Value Integer)
minCapacity :: (Prelude.Maybe (Value Prelude.Integer)),
ScalingConfigurationProperty -> Maybe (Value Integer)
secondsBeforeTimeout :: (Prelude.Maybe (Value Prelude.Integer)),
ScalingConfigurationProperty -> Maybe (Value Integer)
secondsUntilAutoPause :: (Prelude.Maybe (Value Prelude.Integer)),
ScalingConfigurationProperty -> Maybe (Value Text)
timeoutAction :: (Prelude.Maybe (Value Prelude.Text))}
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 :: ScalingConfigurationProperty
mkScalingConfigurationProperty :: ScalingConfigurationProperty
mkScalingConfigurationProperty
= ScalingConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), autoPause :: Maybe (Value Bool)
autoPause = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
maxCapacity :: Maybe (Value Integer)
maxCapacity = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, minCapacity :: Maybe (Value Integer)
minCapacity = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
secondsBeforeTimeout :: Maybe (Value Integer)
secondsBeforeTimeout = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
secondsUntilAutoPause :: Maybe (Value Integer)
secondsUntilAutoPause = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
timeoutAction :: Maybe (Value Text)
timeoutAction = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ScalingConfigurationProperty where
toResourceProperties :: ScalingConfigurationProperty -> ResourceProperties
toResourceProperties ScalingConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ScalingConfigurationProperty -> ()
autoPause :: ScalingConfigurationProperty -> Maybe (Value Bool)
maxCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
minCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsBeforeTimeout :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsUntilAutoPause :: ScalingConfigurationProperty -> Maybe (Value Integer)
timeoutAction :: ScalingConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::RDS::DBCluster.ScalingConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AutoPause" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
autoPause,
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..=) Key
"MaxCapacity" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
maxCapacity,
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..=) Key
"MinCapacity" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
minCapacity,
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..=) Key
"SecondsBeforeTimeout" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
secondsBeforeTimeout,
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..=) Key
"SecondsUntilAutoPause"
(Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
secondsUntilAutoPause,
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..=) Key
"TimeoutAction" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
timeoutAction])}
instance JSON.ToJSON ScalingConfigurationProperty where
toJSON :: ScalingConfigurationProperty -> Value
toJSON ScalingConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ScalingConfigurationProperty -> ()
autoPause :: ScalingConfigurationProperty -> Maybe (Value Bool)
maxCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
minCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsBeforeTimeout :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsUntilAutoPause :: ScalingConfigurationProperty -> Maybe (Value Integer)
timeoutAction :: ScalingConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AutoPause" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
autoPause,
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..=) Key
"MaxCapacity" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
maxCapacity,
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..=) Key
"MinCapacity" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
minCapacity,
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..=) Key
"SecondsBeforeTimeout" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
secondsBeforeTimeout,
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..=) Key
"SecondsUntilAutoPause"
(Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
secondsUntilAutoPause,
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..=) Key
"TimeoutAction" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
timeoutAction]))
instance Property "AutoPause" ScalingConfigurationProperty where
type PropertyType "AutoPause" ScalingConfigurationProperty = Value Prelude.Bool
set :: PropertyType "AutoPause" ScalingConfigurationProperty
-> ScalingConfigurationProperty -> ScalingConfigurationProperty
set PropertyType "AutoPause" ScalingConfigurationProperty
newValue ScalingConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ScalingConfigurationProperty -> ()
autoPause :: ScalingConfigurationProperty -> Maybe (Value Bool)
maxCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
minCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsBeforeTimeout :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsUntilAutoPause :: ScalingConfigurationProperty -> Maybe (Value Integer)
timeoutAction :: ScalingConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
= ScalingConfigurationProperty
{autoPause :: Maybe (Value Bool)
autoPause = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AutoPause" ScalingConfigurationProperty
Value Bool
newValue, Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
haddock_workaround_ :: ()
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
instance Property "MaxCapacity" ScalingConfigurationProperty where
type PropertyType "MaxCapacity" ScalingConfigurationProperty = Value Prelude.Integer
set :: PropertyType "MaxCapacity" ScalingConfigurationProperty
-> ScalingConfigurationProperty -> ScalingConfigurationProperty
set PropertyType "MaxCapacity" ScalingConfigurationProperty
newValue ScalingConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ScalingConfigurationProperty -> ()
autoPause :: ScalingConfigurationProperty -> Maybe (Value Bool)
maxCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
minCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsBeforeTimeout :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsUntilAutoPause :: ScalingConfigurationProperty -> Maybe (Value Integer)
timeoutAction :: ScalingConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
= ScalingConfigurationProperty
{maxCapacity :: Maybe (Value Integer)
maxCapacity = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MaxCapacity" ScalingConfigurationProperty
Value Integer
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
instance Property "MinCapacity" ScalingConfigurationProperty where
type PropertyType "MinCapacity" ScalingConfigurationProperty = Value Prelude.Integer
set :: PropertyType "MinCapacity" ScalingConfigurationProperty
-> ScalingConfigurationProperty -> ScalingConfigurationProperty
set PropertyType "MinCapacity" ScalingConfigurationProperty
newValue ScalingConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ScalingConfigurationProperty -> ()
autoPause :: ScalingConfigurationProperty -> Maybe (Value Bool)
maxCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
minCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsBeforeTimeout :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsUntilAutoPause :: ScalingConfigurationProperty -> Maybe (Value Integer)
timeoutAction :: ScalingConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
= ScalingConfigurationProperty
{minCapacity :: Maybe (Value Integer)
minCapacity = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MinCapacity" ScalingConfigurationProperty
Value Integer
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
instance Property "SecondsBeforeTimeout" ScalingConfigurationProperty where
type PropertyType "SecondsBeforeTimeout" ScalingConfigurationProperty = Value Prelude.Integer
set :: PropertyType "SecondsBeforeTimeout" ScalingConfigurationProperty
-> ScalingConfigurationProperty -> ScalingConfigurationProperty
set PropertyType "SecondsBeforeTimeout" ScalingConfigurationProperty
newValue ScalingConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ScalingConfigurationProperty -> ()
autoPause :: ScalingConfigurationProperty -> Maybe (Value Bool)
maxCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
minCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsBeforeTimeout :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsUntilAutoPause :: ScalingConfigurationProperty -> Maybe (Value Integer)
timeoutAction :: ScalingConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
= ScalingConfigurationProperty
{secondsBeforeTimeout :: Maybe (Value Integer)
secondsBeforeTimeout = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SecondsBeforeTimeout" ScalingConfigurationProperty
Value Integer
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
instance Property "SecondsUntilAutoPause" ScalingConfigurationProperty where
type PropertyType "SecondsUntilAutoPause" ScalingConfigurationProperty = Value Prelude.Integer
set :: PropertyType "SecondsUntilAutoPause" ScalingConfigurationProperty
-> ScalingConfigurationProperty -> ScalingConfigurationProperty
set PropertyType "SecondsUntilAutoPause" ScalingConfigurationProperty
newValue ScalingConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ScalingConfigurationProperty -> ()
autoPause :: ScalingConfigurationProperty -> Maybe (Value Bool)
maxCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
minCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsBeforeTimeout :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsUntilAutoPause :: ScalingConfigurationProperty -> Maybe (Value Integer)
timeoutAction :: ScalingConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
= ScalingConfigurationProperty
{secondsUntilAutoPause :: Maybe (Value Integer)
secondsUntilAutoPause = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SecondsUntilAutoPause" ScalingConfigurationProperty
Value Integer
newValue, Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
instance Property "TimeoutAction" ScalingConfigurationProperty where
type PropertyType "TimeoutAction" ScalingConfigurationProperty = Value Prelude.Text
set :: PropertyType "TimeoutAction" ScalingConfigurationProperty
-> ScalingConfigurationProperty -> ScalingConfigurationProperty
set PropertyType "TimeoutAction" ScalingConfigurationProperty
newValue ScalingConfigurationProperty {Maybe (Value Bool)
Maybe (Value Integer)
Maybe (Value Text)
()
haddock_workaround_ :: ScalingConfigurationProperty -> ()
autoPause :: ScalingConfigurationProperty -> Maybe (Value Bool)
maxCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
minCapacity :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsBeforeTimeout :: ScalingConfigurationProperty -> Maybe (Value Integer)
secondsUntilAutoPause :: ScalingConfigurationProperty -> Maybe (Value Integer)
timeoutAction :: ScalingConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
timeoutAction :: Maybe (Value Text)
..}
= ScalingConfigurationProperty
{timeoutAction :: Maybe (Value Text)
timeoutAction = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TimeoutAction" ScalingConfigurationProperty
Value Text
newValue, Maybe (Value Bool)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
haddock_workaround_ :: ()
autoPause :: Maybe (Value Bool)
maxCapacity :: Maybe (Value Integer)
minCapacity :: Maybe (Value Integer)
secondsBeforeTimeout :: Maybe (Value Integer)
secondsUntilAutoPause :: Maybe (Value Integer)
..}