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