module Stratosphere.ControlTower.EnabledControl.EnabledControlParameterProperty (
        EnabledControlParameterProperty(..),
        mkEnabledControlParameterProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data EnabledControlParameterProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-controltower-enabledcontrol-enabledcontrolparameter.html>
    EnabledControlParameterProperty {EnabledControlParameterProperty -> ()
haddock_workaround_ :: (),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-controltower-enabledcontrol-enabledcontrolparameter.html#cfn-controltower-enabledcontrol-enabledcontrolparameter-key>
                                     EnabledControlParameterProperty -> Value Text
key :: (Value Prelude.Text),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-controltower-enabledcontrol-enabledcontrolparameter.html#cfn-controltower-enabledcontrol-enabledcontrolparameter-value>
                                     EnabledControlParameterProperty -> Object
value :: JSON.Object}
  deriving stock (EnabledControlParameterProperty
-> EnabledControlParameterProperty -> Bool
(EnabledControlParameterProperty
 -> EnabledControlParameterProperty -> Bool)
-> (EnabledControlParameterProperty
    -> EnabledControlParameterProperty -> Bool)
-> Eq EnabledControlParameterProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnabledControlParameterProperty
-> EnabledControlParameterProperty -> Bool
== :: EnabledControlParameterProperty
-> EnabledControlParameterProperty -> Bool
$c/= :: EnabledControlParameterProperty
-> EnabledControlParameterProperty -> Bool
/= :: EnabledControlParameterProperty
-> EnabledControlParameterProperty -> Bool
Prelude.Eq, Int -> EnabledControlParameterProperty -> ShowS
[EnabledControlParameterProperty] -> ShowS
EnabledControlParameterProperty -> String
(Int -> EnabledControlParameterProperty -> ShowS)
-> (EnabledControlParameterProperty -> String)
-> ([EnabledControlParameterProperty] -> ShowS)
-> Show EnabledControlParameterProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EnabledControlParameterProperty -> ShowS
showsPrec :: Int -> EnabledControlParameterProperty -> ShowS
$cshow :: EnabledControlParameterProperty -> String
show :: EnabledControlParameterProperty -> String
$cshowList :: [EnabledControlParameterProperty] -> ShowS
showList :: [EnabledControlParameterProperty] -> ShowS
Prelude.Show)
mkEnabledControlParameterProperty ::
  Value Prelude.Text
  -> JSON.Object -> EnabledControlParameterProperty
mkEnabledControlParameterProperty :: Value Text -> Object -> EnabledControlParameterProperty
mkEnabledControlParameterProperty Value Text
key Object
value
  = EnabledControlParameterProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), key :: Value Text
key = Value Text
key, value :: Object
value = Object
value}
instance ToResourceProperties EnabledControlParameterProperty where
  toResourceProperties :: EnabledControlParameterProperty -> ResourceProperties
toResourceProperties EnabledControlParameterProperty {()
Object
Value Text
haddock_workaround_ :: EnabledControlParameterProperty -> ()
key :: EnabledControlParameterProperty -> Value Text
value :: EnabledControlParameterProperty -> Object
haddock_workaround_ :: ()
key :: Value Text
value :: Object
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::ControlTower::EnabledControl.EnabledControlParameter",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"Key" 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
key, Key
"Value" Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Object
value]}
instance JSON.ToJSON EnabledControlParameterProperty where
  toJSON :: EnabledControlParameterProperty -> Value
toJSON EnabledControlParameterProperty {()
Object
Value Text
haddock_workaround_ :: EnabledControlParameterProperty -> ()
key :: EnabledControlParameterProperty -> Value Text
value :: EnabledControlParameterProperty -> Object
haddock_workaround_ :: ()
key :: Value Text
value :: Object
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"Key" 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
key, Key
"Value" Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Object
value]
instance Property "Key" EnabledControlParameterProperty where
  type PropertyType "Key" EnabledControlParameterProperty = Value Prelude.Text
  set :: PropertyType "Key" EnabledControlParameterProperty
-> EnabledControlParameterProperty
-> EnabledControlParameterProperty
set PropertyType "Key" EnabledControlParameterProperty
newValue EnabledControlParameterProperty {()
Object
Value Text
haddock_workaround_ :: EnabledControlParameterProperty -> ()
key :: EnabledControlParameterProperty -> Value Text
value :: EnabledControlParameterProperty -> Object
haddock_workaround_ :: ()
key :: Value Text
value :: Object
..}
    = EnabledControlParameterProperty {key :: Value Text
key = PropertyType "Key" EnabledControlParameterProperty
Value Text
newValue, ()
Object
haddock_workaround_ :: ()
value :: Object
haddock_workaround_ :: ()
value :: Object
..}
instance Property "Value" EnabledControlParameterProperty where
  type PropertyType "Value" EnabledControlParameterProperty = JSON.Object
  set :: PropertyType "Value" EnabledControlParameterProperty
-> EnabledControlParameterProperty
-> EnabledControlParameterProperty
set PropertyType "Value" EnabledControlParameterProperty
newValue EnabledControlParameterProperty {()
Object
Value Text
haddock_workaround_ :: EnabledControlParameterProperty -> ()
key :: EnabledControlParameterProperty -> Value Text
value :: EnabledControlParameterProperty -> Object
haddock_workaround_ :: ()
key :: Value Text
value :: Object
..}
    = EnabledControlParameterProperty {value :: Object
value = Object
PropertyType "Value" EnabledControlParameterProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
key :: Value Text
haddock_workaround_ :: ()
key :: Value Text
..}