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