module Stratosphere.ARCRegionSwitch.Plan.TriggerConditionProperty (
        TriggerConditionProperty(..), mkTriggerConditionProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data TriggerConditionProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-arcregionswitch-plan-triggercondition.html>
    TriggerConditionProperty {TriggerConditionProperty -> ()
haddock_workaround_ :: (),
                              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-arcregionswitch-plan-triggercondition.html#cfn-arcregionswitch-plan-triggercondition-associatedalarmname>
                              TriggerConditionProperty -> Value Text
associatedAlarmName :: (Value Prelude.Text),
                              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-arcregionswitch-plan-triggercondition.html#cfn-arcregionswitch-plan-triggercondition-condition>
                              TriggerConditionProperty -> Value Text
condition :: (Value Prelude.Text)}
  deriving stock (TriggerConditionProperty -> TriggerConditionProperty -> Bool
(TriggerConditionProperty -> TriggerConditionProperty -> Bool)
-> (TriggerConditionProperty -> TriggerConditionProperty -> Bool)
-> Eq TriggerConditionProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TriggerConditionProperty -> TriggerConditionProperty -> Bool
== :: TriggerConditionProperty -> TriggerConditionProperty -> Bool
$c/= :: TriggerConditionProperty -> TriggerConditionProperty -> Bool
/= :: TriggerConditionProperty -> TriggerConditionProperty -> Bool
Prelude.Eq, Int -> TriggerConditionProperty -> ShowS
[TriggerConditionProperty] -> ShowS
TriggerConditionProperty -> String
(Int -> TriggerConditionProperty -> ShowS)
-> (TriggerConditionProperty -> String)
-> ([TriggerConditionProperty] -> ShowS)
-> Show TriggerConditionProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TriggerConditionProperty -> ShowS
showsPrec :: Int -> TriggerConditionProperty -> ShowS
$cshow :: TriggerConditionProperty -> String
show :: TriggerConditionProperty -> String
$cshowList :: [TriggerConditionProperty] -> ShowS
showList :: [TriggerConditionProperty] -> ShowS
Prelude.Show)
mkTriggerConditionProperty ::
  Value Prelude.Text
  -> Value Prelude.Text -> TriggerConditionProperty
mkTriggerConditionProperty :: Value Text -> Value Text -> TriggerConditionProperty
mkTriggerConditionProperty Value Text
associatedAlarmName Value Text
condition
  = TriggerConditionProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       associatedAlarmName :: Value Text
associatedAlarmName = Value Text
associatedAlarmName, condition :: Value Text
condition = Value Text
condition}
instance ToResourceProperties TriggerConditionProperty where
  toResourceProperties :: TriggerConditionProperty -> ResourceProperties
toResourceProperties TriggerConditionProperty {()
Value Text
haddock_workaround_ :: TriggerConditionProperty -> ()
associatedAlarmName :: TriggerConditionProperty -> Value Text
condition :: TriggerConditionProperty -> Value Text
haddock_workaround_ :: ()
associatedAlarmName :: Value Text
condition :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::ARCRegionSwitch::Plan.TriggerCondition",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"AssociatedAlarmName" 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
associatedAlarmName,
                       Key
"Condition" 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
condition]}
instance JSON.ToJSON TriggerConditionProperty where
  toJSON :: TriggerConditionProperty -> Value
toJSON TriggerConditionProperty {()
Value Text
haddock_workaround_ :: TriggerConditionProperty -> ()
associatedAlarmName :: TriggerConditionProperty -> Value Text
condition :: TriggerConditionProperty -> Value Text
haddock_workaround_ :: ()
associatedAlarmName :: Value Text
condition :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"AssociatedAlarmName" 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
associatedAlarmName,
         Key
"Condition" 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
condition]
instance Property "AssociatedAlarmName" TriggerConditionProperty where
  type PropertyType "AssociatedAlarmName" TriggerConditionProperty = Value Prelude.Text
  set :: PropertyType "AssociatedAlarmName" TriggerConditionProperty
-> TriggerConditionProperty -> TriggerConditionProperty
set PropertyType "AssociatedAlarmName" TriggerConditionProperty
newValue TriggerConditionProperty {()
Value Text
haddock_workaround_ :: TriggerConditionProperty -> ()
associatedAlarmName :: TriggerConditionProperty -> Value Text
condition :: TriggerConditionProperty -> Value Text
haddock_workaround_ :: ()
associatedAlarmName :: Value Text
condition :: Value Text
..}
    = TriggerConditionProperty {associatedAlarmName :: Value Text
associatedAlarmName = PropertyType "AssociatedAlarmName" TriggerConditionProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
condition :: Value Text
haddock_workaround_ :: ()
condition :: Value Text
..}
instance Property "Condition" TriggerConditionProperty where
  type PropertyType "Condition" TriggerConditionProperty = Value Prelude.Text
  set :: PropertyType "Condition" TriggerConditionProperty
-> TriggerConditionProperty -> TriggerConditionProperty
set PropertyType "Condition" TriggerConditionProperty
newValue TriggerConditionProperty {()
Value Text
haddock_workaround_ :: TriggerConditionProperty -> ()
associatedAlarmName :: TriggerConditionProperty -> Value Text
condition :: TriggerConditionProperty -> Value Text
haddock_workaround_ :: ()
associatedAlarmName :: Value Text
condition :: Value Text
..}
    = TriggerConditionProperty {condition :: Value Text
condition = PropertyType "Condition" TriggerConditionProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
associatedAlarmName :: Value Text
haddock_workaround_ :: ()
associatedAlarmName :: Value Text
..}