module Stratosphere.EC2.RouteServerAssociation (
        RouteServerAssociation(..), mkRouteServerAssociation
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RouteServerAssociation
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-routeserverassociation.html>
    RouteServerAssociation {RouteServerAssociation -> ()
haddock_workaround_ :: (),
                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-routeserverassociation.html#cfn-ec2-routeserverassociation-routeserverid>
                            RouteServerAssociation -> Value Text
routeServerId :: (Value Prelude.Text),
                            -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-ec2-routeserverassociation.html#cfn-ec2-routeserverassociation-vpcid>
                            RouteServerAssociation -> Value Text
vpcId :: (Value Prelude.Text)}
  deriving stock (RouteServerAssociation -> RouteServerAssociation -> Bool
(RouteServerAssociation -> RouteServerAssociation -> Bool)
-> (RouteServerAssociation -> RouteServerAssociation -> Bool)
-> Eq RouteServerAssociation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RouteServerAssociation -> RouteServerAssociation -> Bool
== :: RouteServerAssociation -> RouteServerAssociation -> Bool
$c/= :: RouteServerAssociation -> RouteServerAssociation -> Bool
/= :: RouteServerAssociation -> RouteServerAssociation -> Bool
Prelude.Eq, Int -> RouteServerAssociation -> ShowS
[RouteServerAssociation] -> ShowS
RouteServerAssociation -> String
(Int -> RouteServerAssociation -> ShowS)
-> (RouteServerAssociation -> String)
-> ([RouteServerAssociation] -> ShowS)
-> Show RouteServerAssociation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RouteServerAssociation -> ShowS
showsPrec :: Int -> RouteServerAssociation -> ShowS
$cshow :: RouteServerAssociation -> String
show :: RouteServerAssociation -> String
$cshowList :: [RouteServerAssociation] -> ShowS
showList :: [RouteServerAssociation] -> ShowS
Prelude.Show)
mkRouteServerAssociation ::
  Value Prelude.Text -> Value Prelude.Text -> RouteServerAssociation
mkRouteServerAssociation :: Value Text -> Value Text -> RouteServerAssociation
mkRouteServerAssociation Value Text
routeServerId Value Text
vpcId
  = RouteServerAssociation
      {haddock_workaround_ :: ()
haddock_workaround_ = (), routeServerId :: Value Text
routeServerId = Value Text
routeServerId,
       vpcId :: Value Text
vpcId = Value Text
vpcId}
instance ToResourceProperties RouteServerAssociation where
  toResourceProperties :: RouteServerAssociation -> ResourceProperties
toResourceProperties RouteServerAssociation {()
Value Text
haddock_workaround_ :: RouteServerAssociation -> ()
routeServerId :: RouteServerAssociation -> Value Text
vpcId :: RouteServerAssociation -> Value Text
haddock_workaround_ :: ()
routeServerId :: Value Text
vpcId :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::EC2::RouteServerAssociation",
         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
"VpcId" 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
vpcId]}
instance JSON.ToJSON RouteServerAssociation where
  toJSON :: RouteServerAssociation -> Value
toJSON RouteServerAssociation {()
Value Text
haddock_workaround_ :: RouteServerAssociation -> ()
routeServerId :: RouteServerAssociation -> Value Text
vpcId :: RouteServerAssociation -> Value Text
haddock_workaround_ :: ()
routeServerId :: Value Text
vpcId :: 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
"VpcId" 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
vpcId]
instance Property "RouteServerId" RouteServerAssociation where
  type PropertyType "RouteServerId" RouteServerAssociation = Value Prelude.Text
  set :: PropertyType "RouteServerId" RouteServerAssociation
-> RouteServerAssociation -> RouteServerAssociation
set PropertyType "RouteServerId" RouteServerAssociation
newValue RouteServerAssociation {()
Value Text
haddock_workaround_ :: RouteServerAssociation -> ()
routeServerId :: RouteServerAssociation -> Value Text
vpcId :: RouteServerAssociation -> Value Text
haddock_workaround_ :: ()
routeServerId :: Value Text
vpcId :: Value Text
..}
    = RouteServerAssociation {routeServerId :: Value Text
routeServerId = PropertyType "RouteServerId" RouteServerAssociation
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
vpcId :: Value Text
haddock_workaround_ :: ()
vpcId :: Value Text
..}
instance Property "VpcId" RouteServerAssociation where
  type PropertyType "VpcId" RouteServerAssociation = Value Prelude.Text
  set :: PropertyType "VpcId" RouteServerAssociation
-> RouteServerAssociation -> RouteServerAssociation
set PropertyType "VpcId" RouteServerAssociation
newValue RouteServerAssociation {()
Value Text
haddock_workaround_ :: RouteServerAssociation -> ()
routeServerId :: RouteServerAssociation -> Value Text
vpcId :: RouteServerAssociation -> Value Text
haddock_workaround_ :: ()
routeServerId :: Value Text
vpcId :: Value Text
..}
    = RouteServerAssociation {vpcId :: Value Text
vpcId = PropertyType "VpcId" RouteServerAssociation
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
routeServerId :: Value Text
haddock_workaround_ :: ()
routeServerId :: Value Text
..}