module Stratosphere.GreengrassV2.Deployment.IoTJobExponentialRolloutRateProperty (
module Exports, IoTJobExponentialRolloutRateProperty(..),
mkIoTJobExponentialRolloutRateProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.GreengrassV2.Deployment.IoTJobRateIncreaseCriteriaProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data IoTJobExponentialRolloutRateProperty
=
IoTJobExponentialRolloutRateProperty {IoTJobExponentialRolloutRateProperty -> ()
haddock_workaround_ :: (),
IoTJobExponentialRolloutRateProperty -> Value Integer
baseRatePerMinute :: (Value Prelude.Integer),
IoTJobExponentialRolloutRateProperty -> Value Double
incrementFactor :: (Value Prelude.Double),
IoTJobExponentialRolloutRateProperty
-> IoTJobRateIncreaseCriteriaProperty
rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty}
deriving stock (IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty -> Bool
(IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty -> Bool)
-> (IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty -> Bool)
-> Eq IoTJobExponentialRolloutRateProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty -> Bool
== :: IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty -> Bool
$c/= :: IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty -> Bool
/= :: IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty -> Bool
Prelude.Eq, Int -> IoTJobExponentialRolloutRateProperty -> ShowS
[IoTJobExponentialRolloutRateProperty] -> ShowS
IoTJobExponentialRolloutRateProperty -> String
(Int -> IoTJobExponentialRolloutRateProperty -> ShowS)
-> (IoTJobExponentialRolloutRateProperty -> String)
-> ([IoTJobExponentialRolloutRateProperty] -> ShowS)
-> Show IoTJobExponentialRolloutRateProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IoTJobExponentialRolloutRateProperty -> ShowS
showsPrec :: Int -> IoTJobExponentialRolloutRateProperty -> ShowS
$cshow :: IoTJobExponentialRolloutRateProperty -> String
show :: IoTJobExponentialRolloutRateProperty -> String
$cshowList :: [IoTJobExponentialRolloutRateProperty] -> ShowS
showList :: [IoTJobExponentialRolloutRateProperty] -> ShowS
Prelude.Show)
mkIoTJobExponentialRolloutRateProperty ::
Value Prelude.Integer
-> Value Prelude.Double
-> IoTJobRateIncreaseCriteriaProperty
-> IoTJobExponentialRolloutRateProperty
mkIoTJobExponentialRolloutRateProperty :: Value Integer
-> Value Double
-> IoTJobRateIncreaseCriteriaProperty
-> IoTJobExponentialRolloutRateProperty
mkIoTJobExponentialRolloutRateProperty
Value Integer
baseRatePerMinute
Value Double
incrementFactor
IoTJobRateIncreaseCriteriaProperty
rateIncreaseCriteria
= IoTJobExponentialRolloutRateProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), baseRatePerMinute :: Value Integer
baseRatePerMinute = Value Integer
baseRatePerMinute,
incrementFactor :: Value Double
incrementFactor = Value Double
incrementFactor,
rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty
rateIncreaseCriteria = IoTJobRateIncreaseCriteriaProperty
rateIncreaseCriteria}
instance ToResourceProperties IoTJobExponentialRolloutRateProperty where
toResourceProperties :: IoTJobExponentialRolloutRateProperty -> ResourceProperties
toResourceProperties IoTJobExponentialRolloutRateProperty {()
Value Double
Value Integer
IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: IoTJobExponentialRolloutRateProperty -> ()
baseRatePerMinute :: IoTJobExponentialRolloutRateProperty -> Value Integer
incrementFactor :: IoTJobExponentialRolloutRateProperty -> Value Double
rateIncreaseCriteria :: IoTJobExponentialRolloutRateProperty
-> IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: ()
baseRatePerMinute :: Value Integer
incrementFactor :: Value Double
rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::GreengrassV2::Deployment.IoTJobExponentialRolloutRate",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"BaseRatePerMinute" 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
baseRatePerMinute,
Key
"IncrementFactor" 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
incrementFactor,
Key
"RateIncreaseCriteria" Key -> IoTJobRateIncreaseCriteriaProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= IoTJobRateIncreaseCriteriaProperty
rateIncreaseCriteria]}
instance JSON.ToJSON IoTJobExponentialRolloutRateProperty where
toJSON :: IoTJobExponentialRolloutRateProperty -> Value
toJSON IoTJobExponentialRolloutRateProperty {()
Value Double
Value Integer
IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: IoTJobExponentialRolloutRateProperty -> ()
baseRatePerMinute :: IoTJobExponentialRolloutRateProperty -> Value Integer
incrementFactor :: IoTJobExponentialRolloutRateProperty -> Value Double
rateIncreaseCriteria :: IoTJobExponentialRolloutRateProperty
-> IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: ()
baseRatePerMinute :: Value Integer
incrementFactor :: Value Double
rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"BaseRatePerMinute" 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
baseRatePerMinute,
Key
"IncrementFactor" 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
incrementFactor,
Key
"RateIncreaseCriteria" Key -> IoTJobRateIncreaseCriteriaProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= IoTJobRateIncreaseCriteriaProperty
rateIncreaseCriteria]
instance Property "BaseRatePerMinute" IoTJobExponentialRolloutRateProperty where
type PropertyType "BaseRatePerMinute" IoTJobExponentialRolloutRateProperty = Value Prelude.Integer
set :: PropertyType
"BaseRatePerMinute" IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty
set PropertyType
"BaseRatePerMinute" IoTJobExponentialRolloutRateProperty
newValue IoTJobExponentialRolloutRateProperty {()
Value Double
Value Integer
IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: IoTJobExponentialRolloutRateProperty -> ()
baseRatePerMinute :: IoTJobExponentialRolloutRateProperty -> Value Integer
incrementFactor :: IoTJobExponentialRolloutRateProperty -> Value Double
rateIncreaseCriteria :: IoTJobExponentialRolloutRateProperty
-> IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: ()
baseRatePerMinute :: Value Integer
incrementFactor :: Value Double
rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty
..}
= IoTJobExponentialRolloutRateProperty
{baseRatePerMinute :: Value Integer
baseRatePerMinute = PropertyType
"BaseRatePerMinute" IoTJobExponentialRolloutRateProperty
Value Integer
newValue, ()
Value Double
IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: ()
incrementFactor :: Value Double
rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: ()
incrementFactor :: Value Double
rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty
..}
instance Property "IncrementFactor" IoTJobExponentialRolloutRateProperty where
type PropertyType "IncrementFactor" IoTJobExponentialRolloutRateProperty = Value Prelude.Double
set :: PropertyType "IncrementFactor" IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty
set PropertyType "IncrementFactor" IoTJobExponentialRolloutRateProperty
newValue IoTJobExponentialRolloutRateProperty {()
Value Double
Value Integer
IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: IoTJobExponentialRolloutRateProperty -> ()
baseRatePerMinute :: IoTJobExponentialRolloutRateProperty -> Value Integer
incrementFactor :: IoTJobExponentialRolloutRateProperty -> Value Double
rateIncreaseCriteria :: IoTJobExponentialRolloutRateProperty
-> IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: ()
baseRatePerMinute :: Value Integer
incrementFactor :: Value Double
rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty
..}
= IoTJobExponentialRolloutRateProperty
{incrementFactor :: Value Double
incrementFactor = PropertyType "IncrementFactor" IoTJobExponentialRolloutRateProperty
Value Double
newValue, ()
Value Integer
IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: ()
baseRatePerMinute :: Value Integer
rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: ()
baseRatePerMinute :: Value Integer
rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty
..}
instance Property "RateIncreaseCriteria" IoTJobExponentialRolloutRateProperty where
type PropertyType "RateIncreaseCriteria" IoTJobExponentialRolloutRateProperty = IoTJobRateIncreaseCriteriaProperty
set :: PropertyType
"RateIncreaseCriteria" IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty
-> IoTJobExponentialRolloutRateProperty
set PropertyType
"RateIncreaseCriteria" IoTJobExponentialRolloutRateProperty
newValue IoTJobExponentialRolloutRateProperty {()
Value Double
Value Integer
IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: IoTJobExponentialRolloutRateProperty -> ()
baseRatePerMinute :: IoTJobExponentialRolloutRateProperty -> Value Integer
incrementFactor :: IoTJobExponentialRolloutRateProperty -> Value Double
rateIncreaseCriteria :: IoTJobExponentialRolloutRateProperty
-> IoTJobRateIncreaseCriteriaProperty
haddock_workaround_ :: ()
baseRatePerMinute :: Value Integer
incrementFactor :: Value Double
rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty
..}
= IoTJobExponentialRolloutRateProperty
{rateIncreaseCriteria :: IoTJobRateIncreaseCriteriaProperty
rateIncreaseCriteria = PropertyType
"RateIncreaseCriteria" IoTJobExponentialRolloutRateProperty
IoTJobRateIncreaseCriteriaProperty
newValue, ()
Value Double
Value Integer
haddock_workaround_ :: ()
baseRatePerMinute :: Value Integer
incrementFactor :: Value Double
haddock_workaround_ :: ()
baseRatePerMinute :: Value Integer
incrementFactor :: Value Double
..}