module Stratosphere.NetworkManager.ConnectPeer.ConnectPeerConfigurationProperty (
        module Exports, ConnectPeerConfigurationProperty(..),
        mkConnectPeerConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.NetworkManager.ConnectPeer.ConnectPeerBgpConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ConnectPeerConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-networkmanager-connectpeer-connectpeerconfiguration.html>
    ConnectPeerConfigurationProperty {ConnectPeerConfigurationProperty -> ()
haddock_workaround_ :: (),
                                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-networkmanager-connectpeer-connectpeerconfiguration.html#cfn-networkmanager-connectpeer-connectpeerconfiguration-bgpconfigurations>
                                      ConnectPeerConfigurationProperty
-> Maybe [ConnectPeerBgpConfigurationProperty]
bgpConfigurations :: (Prelude.Maybe [ConnectPeerBgpConfigurationProperty]),
                                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-networkmanager-connectpeer-connectpeerconfiguration.html#cfn-networkmanager-connectpeer-connectpeerconfiguration-corenetworkaddress>
                                      ConnectPeerConfigurationProperty -> Maybe (Value Text)
coreNetworkAddress :: (Prelude.Maybe (Value Prelude.Text)),
                                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-networkmanager-connectpeer-connectpeerconfiguration.html#cfn-networkmanager-connectpeer-connectpeerconfiguration-insidecidrblocks>
                                      ConnectPeerConfigurationProperty -> Maybe (ValueList Text)
insideCidrBlocks :: (Prelude.Maybe (ValueList Prelude.Text)),
                                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-networkmanager-connectpeer-connectpeerconfiguration.html#cfn-networkmanager-connectpeer-connectpeerconfiguration-peeraddress>
                                      ConnectPeerConfigurationProperty -> Maybe (Value Text)
peerAddress :: (Prelude.Maybe (Value Prelude.Text)),
                                      -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-networkmanager-connectpeer-connectpeerconfiguration.html#cfn-networkmanager-connectpeer-connectpeerconfiguration-protocol>
                                      ConnectPeerConfigurationProperty -> Maybe (Value Text)
protocol :: (Prelude.Maybe (Value Prelude.Text))}
  deriving stock (ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty -> Bool
(ConnectPeerConfigurationProperty
 -> ConnectPeerConfigurationProperty -> Bool)
-> (ConnectPeerConfigurationProperty
    -> ConnectPeerConfigurationProperty -> Bool)
-> Eq ConnectPeerConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty -> Bool
== :: ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty -> Bool
$c/= :: ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty -> Bool
/= :: ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty -> Bool
Prelude.Eq, Int -> ConnectPeerConfigurationProperty -> ShowS
[ConnectPeerConfigurationProperty] -> ShowS
ConnectPeerConfigurationProperty -> String
(Int -> ConnectPeerConfigurationProperty -> ShowS)
-> (ConnectPeerConfigurationProperty -> String)
-> ([ConnectPeerConfigurationProperty] -> ShowS)
-> Show ConnectPeerConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConnectPeerConfigurationProperty -> ShowS
showsPrec :: Int -> ConnectPeerConfigurationProperty -> ShowS
$cshow :: ConnectPeerConfigurationProperty -> String
show :: ConnectPeerConfigurationProperty -> String
$cshowList :: [ConnectPeerConfigurationProperty] -> ShowS
showList :: [ConnectPeerConfigurationProperty] -> ShowS
Prelude.Show)
mkConnectPeerConfigurationProperty ::
  ConnectPeerConfigurationProperty
mkConnectPeerConfigurationProperty :: ConnectPeerConfigurationProperty
mkConnectPeerConfigurationProperty
  = ConnectPeerConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
bgpConfigurations = Maybe [ConnectPeerBgpConfigurationProperty]
forall a. Maybe a
Prelude.Nothing,
       coreNetworkAddress :: Maybe (Value Text)
coreNetworkAddress = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       insideCidrBlocks :: Maybe (ValueList Text)
insideCidrBlocks = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing, peerAddress :: Maybe (Value Text)
peerAddress = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       protocol :: Maybe (Value Text)
protocol = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ConnectPeerConfigurationProperty where
  toResourceProperties :: ConnectPeerConfigurationProperty -> ResourceProperties
toResourceProperties ConnectPeerConfigurationProperty {Maybe [ConnectPeerBgpConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ConnectPeerConfigurationProperty -> ()
bgpConfigurations :: ConnectPeerConfigurationProperty
-> Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
insideCidrBlocks :: ConnectPeerConfigurationProperty -> Maybe (ValueList Text)
peerAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
protocol :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::NetworkManager::ConnectPeer.ConnectPeerConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
                        ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                           [Key -> [ConnectPeerBgpConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BgpConfigurations" ([ConnectPeerBgpConfigurationProperty] -> (Key, Value))
-> Maybe [ConnectPeerBgpConfigurationProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ConnectPeerBgpConfigurationProperty]
bgpConfigurations,
                            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..=) Key
"CoreNetworkAddress" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
coreNetworkAddress,
                            Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InsideCidrBlocks" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
insideCidrBlocks,
                            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..=) Key
"PeerAddress" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
peerAddress,
                            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..=) Key
"Protocol" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
protocol])}
instance JSON.ToJSON ConnectPeerConfigurationProperty where
  toJSON :: ConnectPeerConfigurationProperty -> Value
toJSON ConnectPeerConfigurationProperty {Maybe [ConnectPeerBgpConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ConnectPeerConfigurationProperty -> ()
bgpConfigurations :: ConnectPeerConfigurationProperty
-> Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
insideCidrBlocks :: ConnectPeerConfigurationProperty -> Maybe (ValueList Text)
peerAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
protocol :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
..}
    = [(Key, Value)] -> Value
JSON.object
        ([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
              [Key -> [ConnectPeerBgpConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BgpConfigurations" ([ConnectPeerBgpConfigurationProperty] -> (Key, Value))
-> Maybe [ConnectPeerBgpConfigurationProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ConnectPeerBgpConfigurationProperty]
bgpConfigurations,
               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..=) Key
"CoreNetworkAddress" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
coreNetworkAddress,
               Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InsideCidrBlocks" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
insideCidrBlocks,
               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..=) Key
"PeerAddress" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
peerAddress,
               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..=) Key
"Protocol" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
protocol]))
instance Property "BgpConfigurations" ConnectPeerConfigurationProperty where
  type PropertyType "BgpConfigurations" ConnectPeerConfigurationProperty = [ConnectPeerBgpConfigurationProperty]
  set :: PropertyType "BgpConfigurations" ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty
set PropertyType "BgpConfigurations" ConnectPeerConfigurationProperty
newValue ConnectPeerConfigurationProperty {Maybe [ConnectPeerBgpConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ConnectPeerConfigurationProperty -> ()
bgpConfigurations :: ConnectPeerConfigurationProperty
-> Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
insideCidrBlocks :: ConnectPeerConfigurationProperty -> Maybe (ValueList Text)
peerAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
protocol :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
..}
    = ConnectPeerConfigurationProperty
        {bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
bgpConfigurations = [ConnectPeerBgpConfigurationProperty]
-> Maybe [ConnectPeerBgpConfigurationProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [ConnectPeerBgpConfigurationProperty]
PropertyType "BgpConfigurations" ConnectPeerConfigurationProperty
newValue, Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ()
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
haddock_workaround_ :: ()
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
..}
instance Property "CoreNetworkAddress" ConnectPeerConfigurationProperty where
  type PropertyType "CoreNetworkAddress" ConnectPeerConfigurationProperty = Value Prelude.Text
  set :: PropertyType "CoreNetworkAddress" ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty
set PropertyType "CoreNetworkAddress" ConnectPeerConfigurationProperty
newValue ConnectPeerConfigurationProperty {Maybe [ConnectPeerBgpConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ConnectPeerConfigurationProperty -> ()
bgpConfigurations :: ConnectPeerConfigurationProperty
-> Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
insideCidrBlocks :: ConnectPeerConfigurationProperty -> Maybe (ValueList Text)
peerAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
protocol :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
..}
    = ConnectPeerConfigurationProperty
        {coreNetworkAddress :: Maybe (Value Text)
coreNetworkAddress = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CoreNetworkAddress" ConnectPeerConfigurationProperty
Value Text
newValue, Maybe [ConnectPeerBgpConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
..}
instance Property "InsideCidrBlocks" ConnectPeerConfigurationProperty where
  type PropertyType "InsideCidrBlocks" ConnectPeerConfigurationProperty = ValueList Prelude.Text
  set :: PropertyType "InsideCidrBlocks" ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty
set PropertyType "InsideCidrBlocks" ConnectPeerConfigurationProperty
newValue ConnectPeerConfigurationProperty {Maybe [ConnectPeerBgpConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ConnectPeerConfigurationProperty -> ()
bgpConfigurations :: ConnectPeerConfigurationProperty
-> Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
insideCidrBlocks :: ConnectPeerConfigurationProperty -> Maybe (ValueList Text)
peerAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
protocol :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
..}
    = ConnectPeerConfigurationProperty
        {insideCidrBlocks :: Maybe (ValueList Text)
insideCidrBlocks = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InsideCidrBlocks" ConnectPeerConfigurationProperty
ValueList Text
newValue, Maybe [ConnectPeerBgpConfigurationProperty]
Maybe (Value Text)
()
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
..}
instance Property "PeerAddress" ConnectPeerConfigurationProperty where
  type PropertyType "PeerAddress" ConnectPeerConfigurationProperty = Value Prelude.Text
  set :: PropertyType "PeerAddress" ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty
set PropertyType "PeerAddress" ConnectPeerConfigurationProperty
newValue ConnectPeerConfigurationProperty {Maybe [ConnectPeerBgpConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ConnectPeerConfigurationProperty -> ()
bgpConfigurations :: ConnectPeerConfigurationProperty
-> Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
insideCidrBlocks :: ConnectPeerConfigurationProperty -> Maybe (ValueList Text)
peerAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
protocol :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
..}
    = ConnectPeerConfigurationProperty
        {peerAddress :: Maybe (Value Text)
peerAddress = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PeerAddress" ConnectPeerConfigurationProperty
Value Text
newValue, Maybe [ConnectPeerBgpConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
protocol :: Maybe (Value Text)
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
protocol :: Maybe (Value Text)
..}
instance Property "Protocol" ConnectPeerConfigurationProperty where
  type PropertyType "Protocol" ConnectPeerConfigurationProperty = Value Prelude.Text
  set :: PropertyType "Protocol" ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty
-> ConnectPeerConfigurationProperty
set PropertyType "Protocol" ConnectPeerConfigurationProperty
newValue ConnectPeerConfigurationProperty {Maybe [ConnectPeerBgpConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ConnectPeerConfigurationProperty -> ()
bgpConfigurations :: ConnectPeerConfigurationProperty
-> Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
insideCidrBlocks :: ConnectPeerConfigurationProperty -> Maybe (ValueList Text)
peerAddress :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
protocol :: ConnectPeerConfigurationProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
protocol :: Maybe (Value Text)
..}
    = ConnectPeerConfigurationProperty
        {protocol :: Maybe (Value Text)
protocol = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Protocol" ConnectPeerConfigurationProperty
Value Text
newValue, Maybe [ConnectPeerBgpConfigurationProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
haddock_workaround_ :: ()
bgpConfigurations :: Maybe [ConnectPeerBgpConfigurationProperty]
coreNetworkAddress :: Maybe (Value Text)
insideCidrBlocks :: Maybe (ValueList Text)
peerAddress :: Maybe (Value Text)
..}