module Stratosphere.EC2.TransitGatewayMulticastGroupSource (
        TransitGatewayMulticastGroupSource(..),
        mkTransitGatewayMulticastGroupSource
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data TransitGatewayMulticastGroupSource
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-transitgatewaymulticastgroupsource.html>
    TransitGatewayMulticastGroupSource {TransitGatewayMulticastGroupSource -> ()
haddock_workaround_ :: (),
                                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-transitgatewaymulticastgroupsource.html#cfn-ec2-transitgatewaymulticastgroupsource-groupipaddress>
                                        TransitGatewayMulticastGroupSource -> Value Text
groupIpAddress :: (Value Prelude.Text),
                                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-transitgatewaymulticastgroupsource.html#cfn-ec2-transitgatewaymulticastgroupsource-networkinterfaceid>
                                        TransitGatewayMulticastGroupSource -> Value Text
networkInterfaceId :: (Value Prelude.Text),
                                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-transitgatewaymulticastgroupsource.html#cfn-ec2-transitgatewaymulticastgroupsource-transitgatewaymulticastdomainid>
                                        TransitGatewayMulticastGroupSource -> Value Text
transitGatewayMulticastDomainId :: (Value Prelude.Text)}
  deriving stock (TransitGatewayMulticastGroupSource
-> TransitGatewayMulticastGroupSource -> Bool
(TransitGatewayMulticastGroupSource
 -> TransitGatewayMulticastGroupSource -> Bool)
-> (TransitGatewayMulticastGroupSource
    -> TransitGatewayMulticastGroupSource -> Bool)
-> Eq TransitGatewayMulticastGroupSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TransitGatewayMulticastGroupSource
-> TransitGatewayMulticastGroupSource -> Bool
== :: TransitGatewayMulticastGroupSource
-> TransitGatewayMulticastGroupSource -> Bool
$c/= :: TransitGatewayMulticastGroupSource
-> TransitGatewayMulticastGroupSource -> Bool
/= :: TransitGatewayMulticastGroupSource
-> TransitGatewayMulticastGroupSource -> Bool
Prelude.Eq, Int -> TransitGatewayMulticastGroupSource -> ShowS
[TransitGatewayMulticastGroupSource] -> ShowS
TransitGatewayMulticastGroupSource -> String
(Int -> TransitGatewayMulticastGroupSource -> ShowS)
-> (TransitGatewayMulticastGroupSource -> String)
-> ([TransitGatewayMulticastGroupSource] -> ShowS)
-> Show TransitGatewayMulticastGroupSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TransitGatewayMulticastGroupSource -> ShowS
showsPrec :: Int -> TransitGatewayMulticastGroupSource -> ShowS
$cshow :: TransitGatewayMulticastGroupSource -> String
show :: TransitGatewayMulticastGroupSource -> String
$cshowList :: [TransitGatewayMulticastGroupSource] -> ShowS
showList :: [TransitGatewayMulticastGroupSource] -> ShowS
Prelude.Show)
mkTransitGatewayMulticastGroupSource ::
  Value Prelude.Text
  -> Value Prelude.Text
     -> Value Prelude.Text -> TransitGatewayMulticastGroupSource
mkTransitGatewayMulticastGroupSource :: Value Text
-> Value Text -> Value Text -> TransitGatewayMulticastGroupSource
mkTransitGatewayMulticastGroupSource
  Value Text
groupIpAddress
  Value Text
networkInterfaceId
  Value Text
transitGatewayMulticastDomainId
  = TransitGatewayMulticastGroupSource
      {haddock_workaround_ :: ()
haddock_workaround_ = (), groupIpAddress :: Value Text
groupIpAddress = Value Text
groupIpAddress,
       networkInterfaceId :: Value Text
networkInterfaceId = Value Text
networkInterfaceId,
       transitGatewayMulticastDomainId :: Value Text
transitGatewayMulticastDomainId = Value Text
transitGatewayMulticastDomainId}
instance ToResourceProperties TransitGatewayMulticastGroupSource where
  toResourceProperties :: TransitGatewayMulticastGroupSource -> ResourceProperties
toResourceProperties TransitGatewayMulticastGroupSource {()
Value Text
haddock_workaround_ :: TransitGatewayMulticastGroupSource -> ()
groupIpAddress :: TransitGatewayMulticastGroupSource -> Value Text
networkInterfaceId :: TransitGatewayMulticastGroupSource -> Value Text
transitGatewayMulticastDomainId :: TransitGatewayMulticastGroupSource -> Value Text
haddock_workaround_ :: ()
groupIpAddress :: Value Text
networkInterfaceId :: Value Text
transitGatewayMulticastDomainId :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::EC2::TransitGatewayMulticastGroupSource",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"GroupIpAddress" 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
groupIpAddress,
                       Key
"NetworkInterfaceId" 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
networkInterfaceId,
                       Key
"TransitGatewayMulticastDomainId"
                         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
transitGatewayMulticastDomainId]}
instance JSON.ToJSON TransitGatewayMulticastGroupSource where
  toJSON :: TransitGatewayMulticastGroupSource -> Value
toJSON TransitGatewayMulticastGroupSource {()
Value Text
haddock_workaround_ :: TransitGatewayMulticastGroupSource -> ()
groupIpAddress :: TransitGatewayMulticastGroupSource -> Value Text
networkInterfaceId :: TransitGatewayMulticastGroupSource -> Value Text
transitGatewayMulticastDomainId :: TransitGatewayMulticastGroupSource -> Value Text
haddock_workaround_ :: ()
groupIpAddress :: Value Text
networkInterfaceId :: Value Text
transitGatewayMulticastDomainId :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"GroupIpAddress" 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
groupIpAddress,
         Key
"NetworkInterfaceId" 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
networkInterfaceId,
         Key
"TransitGatewayMulticastDomainId"
           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
transitGatewayMulticastDomainId]
instance Property "GroupIpAddress" TransitGatewayMulticastGroupSource where
  type PropertyType "GroupIpAddress" TransitGatewayMulticastGroupSource = Value Prelude.Text
  set :: PropertyType "GroupIpAddress" TransitGatewayMulticastGroupSource
-> TransitGatewayMulticastGroupSource
-> TransitGatewayMulticastGroupSource
set PropertyType "GroupIpAddress" TransitGatewayMulticastGroupSource
newValue TransitGatewayMulticastGroupSource {()
Value Text
haddock_workaround_ :: TransitGatewayMulticastGroupSource -> ()
groupIpAddress :: TransitGatewayMulticastGroupSource -> Value Text
networkInterfaceId :: TransitGatewayMulticastGroupSource -> Value Text
transitGatewayMulticastDomainId :: TransitGatewayMulticastGroupSource -> Value Text
haddock_workaround_ :: ()
groupIpAddress :: Value Text
networkInterfaceId :: Value Text
transitGatewayMulticastDomainId :: Value Text
..}
    = TransitGatewayMulticastGroupSource
        {groupIpAddress :: Value Text
groupIpAddress = PropertyType "GroupIpAddress" TransitGatewayMulticastGroupSource
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
networkInterfaceId :: Value Text
transitGatewayMulticastDomainId :: Value Text
haddock_workaround_ :: ()
networkInterfaceId :: Value Text
transitGatewayMulticastDomainId :: Value Text
..}
instance Property "NetworkInterfaceId" TransitGatewayMulticastGroupSource where
  type PropertyType "NetworkInterfaceId" TransitGatewayMulticastGroupSource = Value Prelude.Text
  set :: PropertyType
  "NetworkInterfaceId" TransitGatewayMulticastGroupSource
-> TransitGatewayMulticastGroupSource
-> TransitGatewayMulticastGroupSource
set PropertyType
  "NetworkInterfaceId" TransitGatewayMulticastGroupSource
newValue TransitGatewayMulticastGroupSource {()
Value Text
haddock_workaround_ :: TransitGatewayMulticastGroupSource -> ()
groupIpAddress :: TransitGatewayMulticastGroupSource -> Value Text
networkInterfaceId :: TransitGatewayMulticastGroupSource -> Value Text
transitGatewayMulticastDomainId :: TransitGatewayMulticastGroupSource -> Value Text
haddock_workaround_ :: ()
groupIpAddress :: Value Text
networkInterfaceId :: Value Text
transitGatewayMulticastDomainId :: Value Text
..}
    = TransitGatewayMulticastGroupSource
        {networkInterfaceId :: Value Text
networkInterfaceId = PropertyType
  "NetworkInterfaceId" TransitGatewayMulticastGroupSource
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
groupIpAddress :: Value Text
transitGatewayMulticastDomainId :: Value Text
haddock_workaround_ :: ()
groupIpAddress :: Value Text
transitGatewayMulticastDomainId :: Value Text
..}
instance Property "TransitGatewayMulticastDomainId" TransitGatewayMulticastGroupSource where
  type PropertyType "TransitGatewayMulticastDomainId" TransitGatewayMulticastGroupSource = Value Prelude.Text
  set :: PropertyType
  "TransitGatewayMulticastDomainId"
  TransitGatewayMulticastGroupSource
-> TransitGatewayMulticastGroupSource
-> TransitGatewayMulticastGroupSource
set PropertyType
  "TransitGatewayMulticastDomainId"
  TransitGatewayMulticastGroupSource
newValue TransitGatewayMulticastGroupSource {()
Value Text
haddock_workaround_ :: TransitGatewayMulticastGroupSource -> ()
groupIpAddress :: TransitGatewayMulticastGroupSource -> Value Text
networkInterfaceId :: TransitGatewayMulticastGroupSource -> Value Text
transitGatewayMulticastDomainId :: TransitGatewayMulticastGroupSource -> Value Text
haddock_workaround_ :: ()
groupIpAddress :: Value Text
networkInterfaceId :: Value Text
transitGatewayMulticastDomainId :: Value Text
..}
    = TransitGatewayMulticastGroupSource
        {transitGatewayMulticastDomainId :: Value Text
transitGatewayMulticastDomainId = PropertyType
  "TransitGatewayMulticastDomainId"
  TransitGatewayMulticastGroupSource
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
groupIpAddress :: Value Text
networkInterfaceId :: Value Text
haddock_workaround_ :: ()
groupIpAddress :: Value Text
networkInterfaceId :: Value Text
..}