module Stratosphere.KinesisAnalytics.ApplicationOutput (
module Exports, ApplicationOutput(..), mkApplicationOutput
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.KinesisAnalytics.ApplicationOutput.OutputProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ApplicationOutput
=
ApplicationOutput {ApplicationOutput -> ()
haddock_workaround_ :: (),
ApplicationOutput -> Value Text
applicationName :: (Value Prelude.Text),
ApplicationOutput -> OutputProperty
output :: OutputProperty}
deriving stock (ApplicationOutput -> ApplicationOutput -> Bool
(ApplicationOutput -> ApplicationOutput -> Bool)
-> (ApplicationOutput -> ApplicationOutput -> Bool)
-> Eq ApplicationOutput
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ApplicationOutput -> ApplicationOutput -> Bool
== :: ApplicationOutput -> ApplicationOutput -> Bool
$c/= :: ApplicationOutput -> ApplicationOutput -> Bool
/= :: ApplicationOutput -> ApplicationOutput -> Bool
Prelude.Eq, Int -> ApplicationOutput -> ShowS
[ApplicationOutput] -> ShowS
ApplicationOutput -> String
(Int -> ApplicationOutput -> ShowS)
-> (ApplicationOutput -> String)
-> ([ApplicationOutput] -> ShowS)
-> Show ApplicationOutput
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ApplicationOutput -> ShowS
showsPrec :: Int -> ApplicationOutput -> ShowS
$cshow :: ApplicationOutput -> String
show :: ApplicationOutput -> String
$cshowList :: [ApplicationOutput] -> ShowS
showList :: [ApplicationOutput] -> ShowS
Prelude.Show)
mkApplicationOutput ::
Value Prelude.Text -> OutputProperty -> ApplicationOutput
mkApplicationOutput :: Value Text -> OutputProperty -> ApplicationOutput
mkApplicationOutput Value Text
applicationName OutputProperty
output
= ApplicationOutput
{haddock_workaround_ :: ()
haddock_workaround_ = (), applicationName :: Value Text
applicationName = Value Text
applicationName,
output :: OutputProperty
output = OutputProperty
output}
instance ToResourceProperties ApplicationOutput where
toResourceProperties :: ApplicationOutput -> ResourceProperties
toResourceProperties ApplicationOutput {()
Value Text
OutputProperty
haddock_workaround_ :: ApplicationOutput -> ()
applicationName :: ApplicationOutput -> Value Text
output :: ApplicationOutput -> OutputProperty
haddock_workaround_ :: ()
applicationName :: Value Text
output :: OutputProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::KinesisAnalytics::ApplicationOutput",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"ApplicationName" 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
applicationName,
Key
"Output" Key -> OutputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= OutputProperty
output]}
instance JSON.ToJSON ApplicationOutput where
toJSON :: ApplicationOutput -> Value
toJSON ApplicationOutput {()
Value Text
OutputProperty
haddock_workaround_ :: ApplicationOutput -> ()
applicationName :: ApplicationOutput -> Value Text
output :: ApplicationOutput -> OutputProperty
haddock_workaround_ :: ()
applicationName :: Value Text
output :: OutputProperty
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"ApplicationName" 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
applicationName,
Key
"Output" Key -> OutputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= OutputProperty
output]
instance Property "ApplicationName" ApplicationOutput where
type PropertyType "ApplicationName" ApplicationOutput = Value Prelude.Text
set :: PropertyType "ApplicationName" ApplicationOutput
-> ApplicationOutput -> ApplicationOutput
set PropertyType "ApplicationName" ApplicationOutput
newValue ApplicationOutput {()
Value Text
OutputProperty
haddock_workaround_ :: ApplicationOutput -> ()
applicationName :: ApplicationOutput -> Value Text
output :: ApplicationOutput -> OutputProperty
haddock_workaround_ :: ()
applicationName :: Value Text
output :: OutputProperty
..}
= ApplicationOutput {applicationName :: Value Text
applicationName = PropertyType "ApplicationName" ApplicationOutput
Value Text
newValue, ()
OutputProperty
haddock_workaround_ :: ()
output :: OutputProperty
haddock_workaround_ :: ()
output :: OutputProperty
..}
instance Property "Output" ApplicationOutput where
type PropertyType "Output" ApplicationOutput = OutputProperty
set :: PropertyType "Output" ApplicationOutput
-> ApplicationOutput -> ApplicationOutput
set PropertyType "Output" ApplicationOutput
newValue ApplicationOutput {()
Value Text
OutputProperty
haddock_workaround_ :: ApplicationOutput -> ()
applicationName :: ApplicationOutput -> Value Text
output :: ApplicationOutput -> OutputProperty
haddock_workaround_ :: ()
applicationName :: Value Text
output :: OutputProperty
..}
= ApplicationOutput {output :: OutputProperty
output = PropertyType "Output" ApplicationOutput
OutputProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
applicationName :: Value Text
haddock_workaround_ :: ()
applicationName :: Value Text
..}