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