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