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