module Stratosphere.KinesisAnalytics.ApplicationOutput.KinesisStreamsOutputProperty (
KinesisStreamsOutputProperty(..), mkKinesisStreamsOutputProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data KinesisStreamsOutputProperty
=
KinesisStreamsOutputProperty {KinesisStreamsOutputProperty -> ()
haddock_workaround_ :: (),
KinesisStreamsOutputProperty -> Value Text
resourceARN :: (Value Prelude.Text),
KinesisStreamsOutputProperty -> Value Text
roleARN :: (Value Prelude.Text)}
deriving stock (KinesisStreamsOutputProperty
-> KinesisStreamsOutputProperty -> Bool
(KinesisStreamsOutputProperty
-> KinesisStreamsOutputProperty -> Bool)
-> (KinesisStreamsOutputProperty
-> KinesisStreamsOutputProperty -> Bool)
-> Eq KinesisStreamsOutputProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KinesisStreamsOutputProperty
-> KinesisStreamsOutputProperty -> Bool
== :: KinesisStreamsOutputProperty
-> KinesisStreamsOutputProperty -> Bool
$c/= :: KinesisStreamsOutputProperty
-> KinesisStreamsOutputProperty -> Bool
/= :: KinesisStreamsOutputProperty
-> KinesisStreamsOutputProperty -> Bool
Prelude.Eq, Int -> KinesisStreamsOutputProperty -> ShowS
[KinesisStreamsOutputProperty] -> ShowS
KinesisStreamsOutputProperty -> String
(Int -> KinesisStreamsOutputProperty -> ShowS)
-> (KinesisStreamsOutputProperty -> String)
-> ([KinesisStreamsOutputProperty] -> ShowS)
-> Show KinesisStreamsOutputProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KinesisStreamsOutputProperty -> ShowS
showsPrec :: Int -> KinesisStreamsOutputProperty -> ShowS
$cshow :: KinesisStreamsOutputProperty -> String
show :: KinesisStreamsOutputProperty -> String
$cshowList :: [KinesisStreamsOutputProperty] -> ShowS
showList :: [KinesisStreamsOutputProperty] -> ShowS
Prelude.Show)
mkKinesisStreamsOutputProperty ::
Value Prelude.Text
-> Value Prelude.Text -> KinesisStreamsOutputProperty
mkKinesisStreamsOutputProperty :: Value Text -> Value Text -> KinesisStreamsOutputProperty
mkKinesisStreamsOutputProperty Value Text
resourceARN Value Text
roleARN
= KinesisStreamsOutputProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), resourceARN :: Value Text
resourceARN = Value Text
resourceARN,
roleARN :: Value Text
roleARN = Value Text
roleARN}
instance ToResourceProperties KinesisStreamsOutputProperty where
toResourceProperties :: KinesisStreamsOutputProperty -> ResourceProperties
toResourceProperties KinesisStreamsOutputProperty {()
Value Text
haddock_workaround_ :: KinesisStreamsOutputProperty -> ()
resourceARN :: KinesisStreamsOutputProperty -> Value Text
roleARN :: KinesisStreamsOutputProperty -> Value Text
haddock_workaround_ :: ()
resourceARN :: Value Text
roleARN :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::KinesisAnalytics::ApplicationOutput.KinesisStreamsOutput",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"ResourceARN" 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
resourceARN,
Key
"RoleARN" 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
roleARN]}
instance JSON.ToJSON KinesisStreamsOutputProperty where
toJSON :: KinesisStreamsOutputProperty -> Value
toJSON KinesisStreamsOutputProperty {()
Value Text
haddock_workaround_ :: KinesisStreamsOutputProperty -> ()
resourceARN :: KinesisStreamsOutputProperty -> Value Text
roleARN :: KinesisStreamsOutputProperty -> Value Text
haddock_workaround_ :: ()
resourceARN :: Value Text
roleARN :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"ResourceARN" 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
resourceARN, Key
"RoleARN" 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
roleARN]
instance Property "ResourceARN" KinesisStreamsOutputProperty where
type PropertyType "ResourceARN" KinesisStreamsOutputProperty = Value Prelude.Text
set :: PropertyType "ResourceARN" KinesisStreamsOutputProperty
-> KinesisStreamsOutputProperty -> KinesisStreamsOutputProperty
set PropertyType "ResourceARN" KinesisStreamsOutputProperty
newValue KinesisStreamsOutputProperty {()
Value Text
haddock_workaround_ :: KinesisStreamsOutputProperty -> ()
resourceARN :: KinesisStreamsOutputProperty -> Value Text
roleARN :: KinesisStreamsOutputProperty -> Value Text
haddock_workaround_ :: ()
resourceARN :: Value Text
roleARN :: Value Text
..}
= KinesisStreamsOutputProperty {resourceARN :: Value Text
resourceARN = PropertyType "ResourceARN" KinesisStreamsOutputProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
roleARN :: Value Text
haddock_workaround_ :: ()
roleARN :: Value Text
..}
instance Property "RoleARN" KinesisStreamsOutputProperty where
type PropertyType "RoleARN" KinesisStreamsOutputProperty = Value Prelude.Text
set :: PropertyType "RoleARN" KinesisStreamsOutputProperty
-> KinesisStreamsOutputProperty -> KinesisStreamsOutputProperty
set PropertyType "RoleARN" KinesisStreamsOutputProperty
newValue KinesisStreamsOutputProperty {()
Value Text
haddock_workaround_ :: KinesisStreamsOutputProperty -> ()
resourceARN :: KinesisStreamsOutputProperty -> Value Text
roleARN :: KinesisStreamsOutputProperty -> Value Text
haddock_workaround_ :: ()
resourceARN :: Value Text
roleARN :: Value Text
..}
= KinesisStreamsOutputProperty {roleARN :: Value Text
roleARN = PropertyType "RoleARN" KinesisStreamsOutputProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
resourceARN :: Value Text
haddock_workaround_ :: ()
resourceARN :: Value Text
..}