module Stratosphere.DataPipeline.Pipeline.ParameterObjectProperty (
        module Exports, ParameterObjectProperty(..),
        mkParameterObjectProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.DataPipeline.Pipeline.ParameterAttributeProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ParameterObjectProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-datapipeline-pipeline-parameterobject.html>
    ParameterObjectProperty {ParameterObjectProperty -> ()
haddock_workaround_ :: (),
                             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-datapipeline-pipeline-parameterobject.html#cfn-datapipeline-pipeline-parameterobject-attributes>
                             ParameterObjectProperty -> [ParameterAttributeProperty]
attributes :: [ParameterAttributeProperty],
                             -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-datapipeline-pipeline-parameterobject.html#cfn-datapipeline-pipeline-parameterobject-id>
                             ParameterObjectProperty -> Value Text
id :: (Value Prelude.Text)}
  deriving stock (ParameterObjectProperty -> ParameterObjectProperty -> Bool
(ParameterObjectProperty -> ParameterObjectProperty -> Bool)
-> (ParameterObjectProperty -> ParameterObjectProperty -> Bool)
-> Eq ParameterObjectProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParameterObjectProperty -> ParameterObjectProperty -> Bool
== :: ParameterObjectProperty -> ParameterObjectProperty -> Bool
$c/= :: ParameterObjectProperty -> ParameterObjectProperty -> Bool
/= :: ParameterObjectProperty -> ParameterObjectProperty -> Bool
Prelude.Eq, Int -> ParameterObjectProperty -> ShowS
[ParameterObjectProperty] -> ShowS
ParameterObjectProperty -> String
(Int -> ParameterObjectProperty -> ShowS)
-> (ParameterObjectProperty -> String)
-> ([ParameterObjectProperty] -> ShowS)
-> Show ParameterObjectProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParameterObjectProperty -> ShowS
showsPrec :: Int -> ParameterObjectProperty -> ShowS
$cshow :: ParameterObjectProperty -> String
show :: ParameterObjectProperty -> String
$cshowList :: [ParameterObjectProperty] -> ShowS
showList :: [ParameterObjectProperty] -> ShowS
Prelude.Show)
mkParameterObjectProperty ::
  [ParameterAttributeProperty]
  -> Value Prelude.Text -> ParameterObjectProperty
mkParameterObjectProperty :: [ParameterAttributeProperty]
-> Value Text -> ParameterObjectProperty
mkParameterObjectProperty [ParameterAttributeProperty]
attributes Value Text
id
  = ParameterObjectProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), attributes :: [ParameterAttributeProperty]
attributes = [ParameterAttributeProperty]
attributes, id :: Value Text
id = Value Text
id}
instance ToResourceProperties ParameterObjectProperty where
  toResourceProperties :: ParameterObjectProperty -> ResourceProperties
toResourceProperties ParameterObjectProperty {[ParameterAttributeProperty]
()
Value Text
haddock_workaround_ :: ParameterObjectProperty -> ()
attributes :: ParameterObjectProperty -> [ParameterAttributeProperty]
id :: ParameterObjectProperty -> Value Text
haddock_workaround_ :: ()
attributes :: [ParameterAttributeProperty]
id :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::DataPipeline::Pipeline.ParameterObject",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"Attributes" Key -> [ParameterAttributeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [ParameterAttributeProperty]
attributes, Key
"Id" 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
id]}
instance JSON.ToJSON ParameterObjectProperty where
  toJSON :: ParameterObjectProperty -> Value
toJSON ParameterObjectProperty {[ParameterAttributeProperty]
()
Value Text
haddock_workaround_ :: ParameterObjectProperty -> ()
attributes :: ParameterObjectProperty -> [ParameterAttributeProperty]
id :: ParameterObjectProperty -> Value Text
haddock_workaround_ :: ()
attributes :: [ParameterAttributeProperty]
id :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"Attributes" Key -> [ParameterAttributeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [ParameterAttributeProperty]
attributes, Key
"Id" 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
id]
instance Property "Attributes" ParameterObjectProperty where
  type PropertyType "Attributes" ParameterObjectProperty = [ParameterAttributeProperty]
  set :: PropertyType "Attributes" ParameterObjectProperty
-> ParameterObjectProperty -> ParameterObjectProperty
set PropertyType "Attributes" ParameterObjectProperty
newValue ParameterObjectProperty {[ParameterAttributeProperty]
()
Value Text
haddock_workaround_ :: ParameterObjectProperty -> ()
attributes :: ParameterObjectProperty -> [ParameterAttributeProperty]
id :: ParameterObjectProperty -> Value Text
haddock_workaround_ :: ()
attributes :: [ParameterAttributeProperty]
id :: Value Text
..}
    = ParameterObjectProperty {attributes :: [ParameterAttributeProperty]
attributes = [ParameterAttributeProperty]
PropertyType "Attributes" ParameterObjectProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
id :: Value Text
haddock_workaround_ :: ()
id :: Value Text
..}
instance Property "Id" ParameterObjectProperty where
  type PropertyType "Id" ParameterObjectProperty = Value Prelude.Text
  set :: PropertyType "Id" ParameterObjectProperty
-> ParameterObjectProperty -> ParameterObjectProperty
set PropertyType "Id" ParameterObjectProperty
newValue ParameterObjectProperty {[ParameterAttributeProperty]
()
Value Text
haddock_workaround_ :: ParameterObjectProperty -> ()
attributes :: ParameterObjectProperty -> [ParameterAttributeProperty]
id :: ParameterObjectProperty -> Value Text
haddock_workaround_ :: ()
attributes :: [ParameterAttributeProperty]
id :: Value Text
..}
    = ParameterObjectProperty {id :: Value Text
id = PropertyType "Id" ParameterObjectProperty
Value Text
newValue, [ParameterAttributeProperty]
()
haddock_workaround_ :: ()
attributes :: [ParameterAttributeProperty]
haddock_workaround_ :: ()
attributes :: [ParameterAttributeProperty]
..}