module Stratosphere.DataPipeline.Pipeline.PipelineObjectProperty (
module Exports, PipelineObjectProperty(..),
mkPipelineObjectProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.DataPipeline.Pipeline.FieldProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data PipelineObjectProperty
=
PipelineObjectProperty {PipelineObjectProperty -> ()
haddock_workaround_ :: (),
PipelineObjectProperty -> [FieldProperty]
fields :: [FieldProperty],
PipelineObjectProperty -> Value Text
id :: (Value Prelude.Text),
PipelineObjectProperty -> Value Text
name :: (Value Prelude.Text)}
deriving stock (PipelineObjectProperty -> PipelineObjectProperty -> Bool
(PipelineObjectProperty -> PipelineObjectProperty -> Bool)
-> (PipelineObjectProperty -> PipelineObjectProperty -> Bool)
-> Eq PipelineObjectProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PipelineObjectProperty -> PipelineObjectProperty -> Bool
== :: PipelineObjectProperty -> PipelineObjectProperty -> Bool
$c/= :: PipelineObjectProperty -> PipelineObjectProperty -> Bool
/= :: PipelineObjectProperty -> PipelineObjectProperty -> Bool
Prelude.Eq, Int -> PipelineObjectProperty -> ShowS
[PipelineObjectProperty] -> ShowS
PipelineObjectProperty -> String
(Int -> PipelineObjectProperty -> ShowS)
-> (PipelineObjectProperty -> String)
-> ([PipelineObjectProperty] -> ShowS)
-> Show PipelineObjectProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PipelineObjectProperty -> ShowS
showsPrec :: Int -> PipelineObjectProperty -> ShowS
$cshow :: PipelineObjectProperty -> String
show :: PipelineObjectProperty -> String
$cshowList :: [PipelineObjectProperty] -> ShowS
showList :: [PipelineObjectProperty] -> ShowS
Prelude.Show)
mkPipelineObjectProperty ::
[FieldProperty]
-> Value Prelude.Text
-> Value Prelude.Text -> PipelineObjectProperty
mkPipelineObjectProperty :: [FieldProperty]
-> Value Text -> Value Text -> PipelineObjectProperty
mkPipelineObjectProperty [FieldProperty]
fields Value Text
id Value Text
name
= PipelineObjectProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), fields :: [FieldProperty]
fields = [FieldProperty]
fields, id :: Value Text
id = Value Text
id, name :: Value Text
name = Value Text
name}
instance ToResourceProperties PipelineObjectProperty where
toResourceProperties :: PipelineObjectProperty -> ResourceProperties
toResourceProperties PipelineObjectProperty {[FieldProperty]
()
Value Text
haddock_workaround_ :: PipelineObjectProperty -> ()
fields :: PipelineObjectProperty -> [FieldProperty]
id :: PipelineObjectProperty -> Value Text
name :: PipelineObjectProperty -> Value Text
haddock_workaround_ :: ()
fields :: [FieldProperty]
id :: Value Text
name :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::DataPipeline::Pipeline.PipelineObject",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Fields" Key -> [FieldProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [FieldProperty]
fields, 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,
Key
"Name" 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
name]}
instance JSON.ToJSON PipelineObjectProperty where
toJSON :: PipelineObjectProperty -> Value
toJSON PipelineObjectProperty {[FieldProperty]
()
Value Text
haddock_workaround_ :: PipelineObjectProperty -> ()
fields :: PipelineObjectProperty -> [FieldProperty]
id :: PipelineObjectProperty -> Value Text
name :: PipelineObjectProperty -> Value Text
haddock_workaround_ :: ()
fields :: [FieldProperty]
id :: Value Text
name :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"Fields" Key -> [FieldProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [FieldProperty]
fields, 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, Key
"Name" 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
name]
instance Property "Fields" PipelineObjectProperty where
type PropertyType "Fields" PipelineObjectProperty = [FieldProperty]
set :: PropertyType "Fields" PipelineObjectProperty
-> PipelineObjectProperty -> PipelineObjectProperty
set PropertyType "Fields" PipelineObjectProperty
newValue PipelineObjectProperty {[FieldProperty]
()
Value Text
haddock_workaround_ :: PipelineObjectProperty -> ()
fields :: PipelineObjectProperty -> [FieldProperty]
id :: PipelineObjectProperty -> Value Text
name :: PipelineObjectProperty -> Value Text
haddock_workaround_ :: ()
fields :: [FieldProperty]
id :: Value Text
name :: Value Text
..}
= PipelineObjectProperty {fields :: [FieldProperty]
fields = [FieldProperty]
PropertyType "Fields" PipelineObjectProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
id :: Value Text
name :: Value Text
haddock_workaround_ :: ()
id :: Value Text
name :: Value Text
..}
instance Property "Id" PipelineObjectProperty where
type PropertyType "Id" PipelineObjectProperty = Value Prelude.Text
set :: PropertyType "Id" PipelineObjectProperty
-> PipelineObjectProperty -> PipelineObjectProperty
set PropertyType "Id" PipelineObjectProperty
newValue PipelineObjectProperty {[FieldProperty]
()
Value Text
haddock_workaround_ :: PipelineObjectProperty -> ()
fields :: PipelineObjectProperty -> [FieldProperty]
id :: PipelineObjectProperty -> Value Text
name :: PipelineObjectProperty -> Value Text
haddock_workaround_ :: ()
fields :: [FieldProperty]
id :: Value Text
name :: Value Text
..}
= PipelineObjectProperty {id :: Value Text
id = PropertyType "Id" PipelineObjectProperty
Value Text
newValue, [FieldProperty]
()
Value Text
haddock_workaround_ :: ()
fields :: [FieldProperty]
name :: Value Text
haddock_workaround_ :: ()
fields :: [FieldProperty]
name :: Value Text
..}
instance Property "Name" PipelineObjectProperty where
type PropertyType "Name" PipelineObjectProperty = Value Prelude.Text
set :: PropertyType "Name" PipelineObjectProperty
-> PipelineObjectProperty -> PipelineObjectProperty
set PropertyType "Name" PipelineObjectProperty
newValue PipelineObjectProperty {[FieldProperty]
()
Value Text
haddock_workaround_ :: PipelineObjectProperty -> ()
fields :: PipelineObjectProperty -> [FieldProperty]
id :: PipelineObjectProperty -> Value Text
name :: PipelineObjectProperty -> Value Text
haddock_workaround_ :: ()
fields :: [FieldProperty]
id :: Value Text
name :: Value Text
..}
= PipelineObjectProperty {name :: Value Text
name = PropertyType "Name" PipelineObjectProperty
Value Text
newValue, [FieldProperty]
()
Value Text
haddock_workaround_ :: ()
fields :: [FieldProperty]
id :: Value Text
haddock_workaround_ :: ()
fields :: [FieldProperty]
id :: Value Text
..}