module Stratosphere.MediaConnect.FlowOutput.DestinationConfigurationProperty (
module Exports, DestinationConfigurationProperty(..),
mkDestinationConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.MediaConnect.FlowOutput.InterfaceProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data DestinationConfigurationProperty
=
DestinationConfigurationProperty {DestinationConfigurationProperty -> ()
haddock_workaround_ :: (),
DestinationConfigurationProperty -> Value Text
destinationIp :: (Value Prelude.Text),
DestinationConfigurationProperty -> Value Integer
destinationPort :: (Value Prelude.Integer),
DestinationConfigurationProperty -> InterfaceProperty
interface :: InterfaceProperty}
deriving stock (DestinationConfigurationProperty
-> DestinationConfigurationProperty -> Bool
(DestinationConfigurationProperty
-> DestinationConfigurationProperty -> Bool)
-> (DestinationConfigurationProperty
-> DestinationConfigurationProperty -> Bool)
-> Eq DestinationConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DestinationConfigurationProperty
-> DestinationConfigurationProperty -> Bool
== :: DestinationConfigurationProperty
-> DestinationConfigurationProperty -> Bool
$c/= :: DestinationConfigurationProperty
-> DestinationConfigurationProperty -> Bool
/= :: DestinationConfigurationProperty
-> DestinationConfigurationProperty -> Bool
Prelude.Eq, Int -> DestinationConfigurationProperty -> ShowS
[DestinationConfigurationProperty] -> ShowS
DestinationConfigurationProperty -> String
(Int -> DestinationConfigurationProperty -> ShowS)
-> (DestinationConfigurationProperty -> String)
-> ([DestinationConfigurationProperty] -> ShowS)
-> Show DestinationConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DestinationConfigurationProperty -> ShowS
showsPrec :: Int -> DestinationConfigurationProperty -> ShowS
$cshow :: DestinationConfigurationProperty -> String
show :: DestinationConfigurationProperty -> String
$cshowList :: [DestinationConfigurationProperty] -> ShowS
showList :: [DestinationConfigurationProperty] -> ShowS
Prelude.Show)
mkDestinationConfigurationProperty ::
Value Prelude.Text
-> Value Prelude.Integer
-> InterfaceProperty -> DestinationConfigurationProperty
mkDestinationConfigurationProperty :: Value Text
-> Value Integer
-> InterfaceProperty
-> DestinationConfigurationProperty
mkDestinationConfigurationProperty
Value Text
destinationIp
Value Integer
destinationPort
InterfaceProperty
interface
= DestinationConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), destinationIp :: Value Text
destinationIp = Value Text
destinationIp,
destinationPort :: Value Integer
destinationPort = Value Integer
destinationPort, interface :: InterfaceProperty
interface = InterfaceProperty
interface}
instance ToResourceProperties DestinationConfigurationProperty where
toResourceProperties :: DestinationConfigurationProperty -> ResourceProperties
toResourceProperties DestinationConfigurationProperty {()
Value Integer
Value Text
InterfaceProperty
haddock_workaround_ :: DestinationConfigurationProperty -> ()
destinationIp :: DestinationConfigurationProperty -> Value Text
destinationPort :: DestinationConfigurationProperty -> Value Integer
interface :: DestinationConfigurationProperty -> InterfaceProperty
haddock_workaround_ :: ()
destinationIp :: Value Text
destinationPort :: Value Integer
interface :: InterfaceProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::MediaConnect::FlowOutput.DestinationConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"DestinationIp" 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
destinationIp,
Key
"DestinationPort" Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Integer
destinationPort,
Key
"Interface" Key -> InterfaceProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= InterfaceProperty
interface]}
instance JSON.ToJSON DestinationConfigurationProperty where
toJSON :: DestinationConfigurationProperty -> Value
toJSON DestinationConfigurationProperty {()
Value Integer
Value Text
InterfaceProperty
haddock_workaround_ :: DestinationConfigurationProperty -> ()
destinationIp :: DestinationConfigurationProperty -> Value Text
destinationPort :: DestinationConfigurationProperty -> Value Integer
interface :: DestinationConfigurationProperty -> InterfaceProperty
haddock_workaround_ :: ()
destinationIp :: Value Text
destinationPort :: Value Integer
interface :: InterfaceProperty
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"DestinationIp" 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
destinationIp,
Key
"DestinationPort" Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Integer
destinationPort,
Key
"Interface" Key -> InterfaceProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= InterfaceProperty
interface]
instance Property "DestinationIp" DestinationConfigurationProperty where
type PropertyType "DestinationIp" DestinationConfigurationProperty = Value Prelude.Text
set :: PropertyType "DestinationIp" DestinationConfigurationProperty
-> DestinationConfigurationProperty
-> DestinationConfigurationProperty
set PropertyType "DestinationIp" DestinationConfigurationProperty
newValue DestinationConfigurationProperty {()
Value Integer
Value Text
InterfaceProperty
haddock_workaround_ :: DestinationConfigurationProperty -> ()
destinationIp :: DestinationConfigurationProperty -> Value Text
destinationPort :: DestinationConfigurationProperty -> Value Integer
interface :: DestinationConfigurationProperty -> InterfaceProperty
haddock_workaround_ :: ()
destinationIp :: Value Text
destinationPort :: Value Integer
interface :: InterfaceProperty
..}
= DestinationConfigurationProperty {destinationIp :: Value Text
destinationIp = PropertyType "DestinationIp" DestinationConfigurationProperty
Value Text
newValue, ()
Value Integer
InterfaceProperty
haddock_workaround_ :: ()
destinationPort :: Value Integer
interface :: InterfaceProperty
haddock_workaround_ :: ()
destinationPort :: Value Integer
interface :: InterfaceProperty
..}
instance Property "DestinationPort" DestinationConfigurationProperty where
type PropertyType "DestinationPort" DestinationConfigurationProperty = Value Prelude.Integer
set :: PropertyType "DestinationPort" DestinationConfigurationProperty
-> DestinationConfigurationProperty
-> DestinationConfigurationProperty
set PropertyType "DestinationPort" DestinationConfigurationProperty
newValue DestinationConfigurationProperty {()
Value Integer
Value Text
InterfaceProperty
haddock_workaround_ :: DestinationConfigurationProperty -> ()
destinationIp :: DestinationConfigurationProperty -> Value Text
destinationPort :: DestinationConfigurationProperty -> Value Integer
interface :: DestinationConfigurationProperty -> InterfaceProperty
haddock_workaround_ :: ()
destinationIp :: Value Text
destinationPort :: Value Integer
interface :: InterfaceProperty
..}
= DestinationConfigurationProperty {destinationPort :: Value Integer
destinationPort = PropertyType "DestinationPort" DestinationConfigurationProperty
Value Integer
newValue, ()
Value Text
InterfaceProperty
haddock_workaround_ :: ()
destinationIp :: Value Text
interface :: InterfaceProperty
haddock_workaround_ :: ()
destinationIp :: Value Text
interface :: InterfaceProperty
..}
instance Property "Interface" DestinationConfigurationProperty where
type PropertyType "Interface" DestinationConfigurationProperty = InterfaceProperty
set :: PropertyType "Interface" DestinationConfigurationProperty
-> DestinationConfigurationProperty
-> DestinationConfigurationProperty
set PropertyType "Interface" DestinationConfigurationProperty
newValue DestinationConfigurationProperty {()
Value Integer
Value Text
InterfaceProperty
haddock_workaround_ :: DestinationConfigurationProperty -> ()
destinationIp :: DestinationConfigurationProperty -> Value Text
destinationPort :: DestinationConfigurationProperty -> Value Integer
interface :: DestinationConfigurationProperty -> InterfaceProperty
haddock_workaround_ :: ()
destinationIp :: Value Text
destinationPort :: Value Integer
interface :: InterfaceProperty
..}
= DestinationConfigurationProperty {interface :: InterfaceProperty
interface = PropertyType "Interface" DestinationConfigurationProperty
InterfaceProperty
newValue, ()
Value Integer
Value Text
haddock_workaround_ :: ()
destinationIp :: Value Text
destinationPort :: Value Integer
haddock_workaround_ :: ()
destinationIp :: Value Text
destinationPort :: Value Integer
..}