amazonka-directconnect-1.6.0: Amazon Direct Connect SDK.

Copyright(c) 2013-2018 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay+amazonka@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS.DirectConnect

Contents

Description

AWS Direct Connect links your internal network to an AWS Direct Connect location over a standard 1 gigabit or 10 gigabit Ethernet fiber-optic cable. One end of the cable is connected to your router, the other to an AWS Direct Connect router. With this connection in place, you can create virtual interfaces directly to the AWS cloud (for example, to Amazon Elastic Compute Cloud (Amazon EC2) and Amazon Simple Storage Service (Amazon S3)) and to Amazon Virtual Private Cloud (Amazon VPC), bypassing Internet service providers in your network path. An AWS Direct Connect location provides access to AWS in the region it is associated with, as well as access to other US regions. For example, you can provision a single connection to any AWS Direct Connect location in the US and use it to access public AWS services in all US Regions and AWS GovCloud (US).

Synopsis

Service Configuration

directConnect :: Service Source #

API version 2012-10-25 of the Amazon Direct Connect SDK configuration.

Errors

Error matchers are designed for use with the functions provided by Control.Exception.Lens. This allows catching (and rethrowing) service specific errors returned by DirectConnect.

DirectConnectClientException

_DirectConnectClientException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The API was called with invalid parameters. The error message will contain additional details about the cause.

DuplicateTagKeysException

_DuplicateTagKeysException :: AsError a => Getting (First ServiceError) a ServiceError Source #

A tag key was specified more than once.

TooManyTagsException

_TooManyTagsException :: AsError a => Getting (First ServiceError) a ServiceError Source #

You have reached the limit on the number of tags that can be assigned to a Direct Connect resource.

DirectConnectServerException

_DirectConnectServerException :: AsError a => Getting (First ServiceError) a ServiceError Source #

A server-side error occurred during the API call. The error message will contain additional details about the cause.

Waiters

Waiters poll by repeatedly sending a request until some remote success condition configured by the Wait specification is fulfilled. The Wait specification determines how many attempts should be made, in addition to delay and retry strategies.

Operations

Some AWS operations return results that are incomplete and require subsequent requests in order to obtain the entire result set. The process of sending subsequent requests to continue where a previous request left off is called pagination. For example, the ListObjects operation of Amazon S3 returns up to 1000 objects at a time, and you must send subsequent requests with the appropriate Marker in order to retrieve the next page of results.

Operations that have an AWSPager instance can transparently perform subsequent requests, correctly setting Markers and other request facets to iterate through the entire result set of a truncated API operation. Operations which support this have an additional note in the documentation.

Many operations have the ability to filter results on the server side. See the individual operation parameters for details.

DescribeDirectConnectGatewayAssociations

DescribeInterconnects

DescribeTags

DescribeLoa

DeleteConnection

AssociateConnectionWithLag

CreateConnection

DescribeDirectConnectGateways

AssociateVirtualInterface

DescribeConnections

DeleteInterconnect

ConfirmPrivateVirtualInterface

DeleteDirectConnectGatewayAssociation

DescribeLocations

CreateDirectConnectGatewayAssociation

CreatePublicVirtualInterface

AllocatePrivateVirtualInterface

DescribeLags

ConfirmConnection

DescribeDirectConnectGatewayAttachments

ConfirmPublicVirtualInterface

DescribeVirtualGateways

CreateDirectConnectGateway

DeleteDirectConnectGateway

DescribeVirtualInterfaces

AllocateHostedConnection

DeleteVirtualInterface

CreatePrivateVirtualInterface

AllocatePublicVirtualInterface

DisassociateConnectionFromLag

TagResource

DeleteLag

UpdateLag

UntagResource

CreateBGPPeer

AssociateHostedConnection

CreateInterconnect

DeleteBGPPeer

CreateLag

DescribeHostedConnections

Types

AddressFamily

data AddressFamily Source #

Indicates the address family for the BGP peer.

  • ipv4 : IPv4 address family
  • ipv6 : IPv6 address family

Constructors

IPV4 
IPV6 

Instances

Bounded AddressFamily Source # 
Enum AddressFamily Source # 
Eq AddressFamily Source # 
Data AddressFamily Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddressFamily -> c AddressFamily #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddressFamily #

toConstr :: AddressFamily -> Constr #

dataTypeOf :: AddressFamily -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddressFamily) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddressFamily) #

gmapT :: (forall b. Data b => b -> b) -> AddressFamily -> AddressFamily #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddressFamily -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddressFamily -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddressFamily -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddressFamily -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddressFamily -> m AddressFamily #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressFamily -> m AddressFamily #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressFamily -> m AddressFamily #

Ord AddressFamily Source # 
Read AddressFamily Source # 
Show AddressFamily Source # 
Generic AddressFamily Source # 

Associated Types

type Rep AddressFamily :: * -> * #

Hashable AddressFamily Source # 
ToJSON AddressFamily Source # 
FromJSON AddressFamily Source # 
NFData AddressFamily Source # 

Methods

rnf :: AddressFamily -> () #

ToHeader AddressFamily Source # 
ToQuery AddressFamily Source # 
ToByteString AddressFamily Source # 
FromText AddressFamily Source # 
ToText AddressFamily Source # 

Methods

toText :: AddressFamily -> Text #

type Rep AddressFamily Source # 
type Rep AddressFamily = D1 * (MetaData "AddressFamily" "Network.AWS.DirectConnect.Types.Sum" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) ((:+:) * (C1 * (MetaCons "IPV4" PrefixI False) (U1 *)) (C1 * (MetaCons "IPV6" PrefixI False) (U1 *)))

BGPPeerState

data BGPPeerState Source #

The state of the BGP peer.

  • Verifying : The BGP peering addresses or ASN require validation before the BGP peer can be created. This state only applies to BGP peers on a public virtual interface.
  • Pending : The BGP peer has been created, and is in this state until it is ready to be established.
  • Available : The BGP peer can be established.
  • Deleting : The BGP peer is in the process of being deleted.
  • Deleted : The BGP peer has been deleted and cannot be established.

Instances

Bounded BGPPeerState Source # 
Enum BGPPeerState Source # 
Eq BGPPeerState Source # 
Data BGPPeerState Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BGPPeerState -> c BGPPeerState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BGPPeerState #

toConstr :: BGPPeerState -> Constr #

dataTypeOf :: BGPPeerState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BGPPeerState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BGPPeerState) #

gmapT :: (forall b. Data b => b -> b) -> BGPPeerState -> BGPPeerState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BGPPeerState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BGPPeerState -> r #

gmapQ :: (forall d. Data d => d -> u) -> BGPPeerState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BGPPeerState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BGPPeerState -> m BGPPeerState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BGPPeerState -> m BGPPeerState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BGPPeerState -> m BGPPeerState #

Ord BGPPeerState Source # 
Read BGPPeerState Source # 
Show BGPPeerState Source # 
Generic BGPPeerState Source # 

Associated Types

type Rep BGPPeerState :: * -> * #

Hashable BGPPeerState Source # 
FromJSON BGPPeerState Source # 
NFData BGPPeerState Source # 

Methods

rnf :: BGPPeerState -> () #

ToHeader BGPPeerState Source # 
ToQuery BGPPeerState Source # 
ToByteString BGPPeerState Source # 
FromText BGPPeerState Source # 
ToText BGPPeerState Source # 

Methods

toText :: BGPPeerState -> Text #

type Rep BGPPeerState Source # 
type Rep BGPPeerState = D1 * (MetaData "BGPPeerState" "Network.AWS.DirectConnect.Types.Sum" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Available" PrefixI False) (U1 *)) (C1 * (MetaCons "Deleted" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Deleting" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Pending" PrefixI False) (U1 *)) (C1 * (MetaCons "Verifying" PrefixI False) (U1 *)))))

BGPStatus

data BGPStatus Source #

The Up/Down state of the BGP peer.

  • Up : The BGP peer is established.
  • Down : The BGP peer is down.

Constructors

Down 
UP 

Instances

Bounded BGPStatus Source # 
Enum BGPStatus Source # 
Eq BGPStatus Source # 
Data BGPStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BGPStatus -> c BGPStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BGPStatus #

toConstr :: BGPStatus -> Constr #

dataTypeOf :: BGPStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BGPStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BGPStatus) #

gmapT :: (forall b. Data b => b -> b) -> BGPStatus -> BGPStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BGPStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BGPStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> BGPStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BGPStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BGPStatus -> m BGPStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BGPStatus -> m BGPStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BGPStatus -> m BGPStatus #

Ord BGPStatus Source # 
Read BGPStatus Source # 
Show BGPStatus Source # 
Generic BGPStatus Source # 

Associated Types

type Rep BGPStatus :: * -> * #

Hashable BGPStatus Source # 
FromJSON BGPStatus Source # 
NFData BGPStatus Source # 

Methods

rnf :: BGPStatus -> () #

ToHeader BGPStatus Source # 
ToQuery BGPStatus Source # 
ToByteString BGPStatus Source # 

Methods

toBS :: BGPStatus -> ByteString #

FromText BGPStatus Source # 
ToText BGPStatus Source # 

Methods

toText :: BGPStatus -> Text #

type Rep BGPStatus Source # 
type Rep BGPStatus = D1 * (MetaData "BGPStatus" "Network.AWS.DirectConnect.Types.Sum" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) ((:+:) * (C1 * (MetaCons "Down" PrefixI False) (U1 *)) (C1 * (MetaCons "UP" PrefixI False) (U1 *)))

ConnectionState

data ConnectionState Source #

State of the connection.

  • Ordering : The initial state of a hosted connection provisioned on an interconnect. The connection stays in the ordering state until the owner of the hosted connection confirms or declines the connection order.
  • Requested : The initial state of a standard connection. The connection stays in the requested state until the Letter of Authorization (LOA) is sent to the customer.
  • Pending : The connection has been approved, and is being initialized.
  • Available : The network link is up, and the connection is ready for use.
  • Down : The network link is down.
  • Deleting : The connection is in the process of being deleted.
  • Deleted : The connection has been deleted.
  • Rejected : A hosted connection in the Ordering state will enter the Rejected state if it is deleted by the end customer.

Instances

Bounded ConnectionState Source # 
Enum ConnectionState Source # 
Eq ConnectionState Source # 
Data ConnectionState Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConnectionState -> c ConnectionState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConnectionState #

toConstr :: ConnectionState -> Constr #

dataTypeOf :: ConnectionState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConnectionState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConnectionState) #

gmapT :: (forall b. Data b => b -> b) -> ConnectionState -> ConnectionState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConnectionState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConnectionState -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConnectionState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConnectionState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConnectionState -> m ConnectionState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectionState -> m ConnectionState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectionState -> m ConnectionState #

Ord ConnectionState Source # 
Read ConnectionState Source # 
Show ConnectionState Source # 
Generic ConnectionState Source # 
Hashable ConnectionState Source # 
FromJSON ConnectionState Source # 
NFData ConnectionState Source # 

Methods

rnf :: ConnectionState -> () #

ToHeader ConnectionState Source # 
ToQuery ConnectionState Source # 
ToByteString ConnectionState Source # 
FromText ConnectionState Source # 
ToText ConnectionState Source # 
type Rep ConnectionState Source # 
type Rep ConnectionState = D1 * (MetaData "ConnectionState" "Network.AWS.DirectConnect.Types.Sum" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CSAvailable" PrefixI False) (U1 *)) (C1 * (MetaCons "CSDeleted" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CSDeleting" PrefixI False) (U1 *)) (C1 * (MetaCons "CSDown" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CSOrdering" PrefixI False) (U1 *)) (C1 * (MetaCons "CSPending" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CSRejected" PrefixI False) (U1 *)) (C1 * (MetaCons "CSRequested" PrefixI False) (U1 *)))))

DirectConnectGatewayAssociationState

data DirectConnectGatewayAssociationState Source #

State of the direct connect gateway association.

  • Associating : The initial state after calling CreateDirectConnectGatewayAssociation .
  • Associated : The direct connect gateway and virtual private gateway are successfully associated and ready to pass traffic.
  • Disassociating : The initial state after calling DeleteDirectConnectGatewayAssociation .
  • Disassociated : The virtual private gateway is successfully disassociated from the direct connect gateway. Traffic flow between the direct connect gateway and virtual private gateway stops.

Instances

Bounded DirectConnectGatewayAssociationState Source # 
Enum DirectConnectGatewayAssociationState Source # 
Eq DirectConnectGatewayAssociationState Source # 
Data DirectConnectGatewayAssociationState Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectConnectGatewayAssociationState -> c DirectConnectGatewayAssociationState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectConnectGatewayAssociationState #

toConstr :: DirectConnectGatewayAssociationState -> Constr #

dataTypeOf :: DirectConnectGatewayAssociationState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectConnectGatewayAssociationState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectConnectGatewayAssociationState) #

gmapT :: (forall b. Data b => b -> b) -> DirectConnectGatewayAssociationState -> DirectConnectGatewayAssociationState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGatewayAssociationState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGatewayAssociationState -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectConnectGatewayAssociationState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectConnectGatewayAssociationState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAssociationState -> m DirectConnectGatewayAssociationState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAssociationState -> m DirectConnectGatewayAssociationState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAssociationState -> m DirectConnectGatewayAssociationState #

Ord DirectConnectGatewayAssociationState Source # 
Read DirectConnectGatewayAssociationState Source # 
Show DirectConnectGatewayAssociationState Source # 
Generic DirectConnectGatewayAssociationState Source # 
Hashable DirectConnectGatewayAssociationState Source # 
FromJSON DirectConnectGatewayAssociationState Source # 
NFData DirectConnectGatewayAssociationState Source # 
ToHeader DirectConnectGatewayAssociationState Source # 
ToQuery DirectConnectGatewayAssociationState Source # 
ToByteString DirectConnectGatewayAssociationState Source # 
FromText DirectConnectGatewayAssociationState Source # 
ToText DirectConnectGatewayAssociationState Source # 
type Rep DirectConnectGatewayAssociationState Source # 
type Rep DirectConnectGatewayAssociationState = D1 * (MetaData "DirectConnectGatewayAssociationState" "Network.AWS.DirectConnect.Types.Sum" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Associated" PrefixI False) (U1 *)) (C1 * (MetaCons "Associating" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Disassociated" PrefixI False) (U1 *)) (C1 * (MetaCons "Disassociating" PrefixI False) (U1 *))))

DirectConnectGatewayAttachmentState

data DirectConnectGatewayAttachmentState Source #

State of the direct connect gateway attachment.

  • Attaching : The initial state after a virtual interface is created using the direct connect gateway.
  • Attached : The direct connect gateway and virtual interface are successfully attached and ready to pass traffic.
  • Detaching : The initial state after calling DeleteVirtualInterface on a virtual interface that is attached to a direct connect gateway.
  • Detached : The virtual interface is successfully detached from the direct connect gateway. Traffic flow between the direct connect gateway and virtual interface stops.

Instances

Bounded DirectConnectGatewayAttachmentState Source # 
Enum DirectConnectGatewayAttachmentState Source # 
Eq DirectConnectGatewayAttachmentState Source # 
Data DirectConnectGatewayAttachmentState Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectConnectGatewayAttachmentState -> c DirectConnectGatewayAttachmentState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectConnectGatewayAttachmentState #

toConstr :: DirectConnectGatewayAttachmentState -> Constr #

dataTypeOf :: DirectConnectGatewayAttachmentState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectConnectGatewayAttachmentState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectConnectGatewayAttachmentState) #

gmapT :: (forall b. Data b => b -> b) -> DirectConnectGatewayAttachmentState -> DirectConnectGatewayAttachmentState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGatewayAttachmentState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGatewayAttachmentState -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectConnectGatewayAttachmentState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectConnectGatewayAttachmentState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAttachmentState -> m DirectConnectGatewayAttachmentState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAttachmentState -> m DirectConnectGatewayAttachmentState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAttachmentState -> m DirectConnectGatewayAttachmentState #

Ord DirectConnectGatewayAttachmentState Source # 
Read DirectConnectGatewayAttachmentState Source # 
Show DirectConnectGatewayAttachmentState Source # 
Generic DirectConnectGatewayAttachmentState Source # 
Hashable DirectConnectGatewayAttachmentState Source # 
FromJSON DirectConnectGatewayAttachmentState Source # 
NFData DirectConnectGatewayAttachmentState Source # 
ToHeader DirectConnectGatewayAttachmentState Source # 
ToQuery DirectConnectGatewayAttachmentState Source # 
ToByteString DirectConnectGatewayAttachmentState Source # 
FromText DirectConnectGatewayAttachmentState Source # 
ToText DirectConnectGatewayAttachmentState Source # 
type Rep DirectConnectGatewayAttachmentState Source # 
type Rep DirectConnectGatewayAttachmentState = D1 * (MetaData "DirectConnectGatewayAttachmentState" "Network.AWS.DirectConnect.Types.Sum" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Attached" PrefixI False) (U1 *)) (C1 * (MetaCons "Attaching" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Detached" PrefixI False) (U1 *)) (C1 * (MetaCons "Detaching" PrefixI False) (U1 *))))

DirectConnectGatewayState

data DirectConnectGatewayState Source #

State of the direct connect gateway.

  • Pending : The initial state after calling CreateDirectConnectGateway .
  • Available : The direct connect gateway is ready for use.
  • Deleting : The initial state after calling DeleteDirectConnectGateway .
  • Deleted : The direct connect gateway is deleted and cannot pass traffic.

Instances

Bounded DirectConnectGatewayState Source # 
Enum DirectConnectGatewayState Source # 
Eq DirectConnectGatewayState Source # 
Data DirectConnectGatewayState Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectConnectGatewayState -> c DirectConnectGatewayState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectConnectGatewayState #

toConstr :: DirectConnectGatewayState -> Constr #

dataTypeOf :: DirectConnectGatewayState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectConnectGatewayState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectConnectGatewayState) #

gmapT :: (forall b. Data b => b -> b) -> DirectConnectGatewayState -> DirectConnectGatewayState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGatewayState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGatewayState -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectConnectGatewayState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectConnectGatewayState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectConnectGatewayState -> m DirectConnectGatewayState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGatewayState -> m DirectConnectGatewayState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGatewayState -> m DirectConnectGatewayState #

Ord DirectConnectGatewayState Source # 
Read DirectConnectGatewayState Source # 
Show DirectConnectGatewayState Source # 
Generic DirectConnectGatewayState Source # 
Hashable DirectConnectGatewayState Source # 
FromJSON DirectConnectGatewayState Source # 
NFData DirectConnectGatewayState Source # 
ToHeader DirectConnectGatewayState Source # 
ToQuery DirectConnectGatewayState Source # 
ToByteString DirectConnectGatewayState Source # 
FromText DirectConnectGatewayState Source # 
ToText DirectConnectGatewayState Source # 
type Rep DirectConnectGatewayState Source # 
type Rep DirectConnectGatewayState = D1 * (MetaData "DirectConnectGatewayState" "Network.AWS.DirectConnect.Types.Sum" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "DCGSAvailable" PrefixI False) (U1 *)) (C1 * (MetaCons "DCGSDeleted" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "DCGSDeleting" PrefixI False) (U1 *)) (C1 * (MetaCons "DCGSPending" PrefixI False) (U1 *))))

InterconnectState

data InterconnectState Source #

State of the interconnect.

  • Requested : The initial state of an interconnect. The interconnect stays in the requested state until the Letter of Authorization (LOA) is sent to the customer.
  • Pending : The interconnect has been approved, and is being initialized.
  • Available : The network link is up, and the interconnect is ready for use.
  • Down : The network link is down.
  • Deleting : The interconnect is in the process of being deleted.
  • Deleted : The interconnect has been deleted.

Instances

Bounded InterconnectState Source # 
Enum InterconnectState Source # 
Eq InterconnectState Source # 
Data InterconnectState Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InterconnectState -> c InterconnectState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InterconnectState #

toConstr :: InterconnectState -> Constr #

dataTypeOf :: InterconnectState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InterconnectState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InterconnectState) #

gmapT :: (forall b. Data b => b -> b) -> InterconnectState -> InterconnectState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InterconnectState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InterconnectState -> r #

gmapQ :: (forall d. Data d => d -> u) -> InterconnectState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InterconnectState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InterconnectState -> m InterconnectState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InterconnectState -> m InterconnectState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InterconnectState -> m InterconnectState #

Ord InterconnectState Source # 
Read InterconnectState Source # 
Show InterconnectState Source # 
Generic InterconnectState Source # 
Hashable InterconnectState Source # 
FromJSON InterconnectState Source # 
NFData InterconnectState Source # 

Methods

rnf :: InterconnectState -> () #

ToHeader InterconnectState Source # 
ToQuery InterconnectState Source # 
ToByteString InterconnectState Source # 
FromText InterconnectState Source # 
ToText InterconnectState Source # 
type Rep InterconnectState Source # 
type Rep InterconnectState = D1 * (MetaData "InterconnectState" "Network.AWS.DirectConnect.Types.Sum" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ISAvailable" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ISDeleted" PrefixI False) (U1 *)) (C1 * (MetaCons "ISDeleting" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "ISDown" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ISPending" PrefixI False) (U1 *)) (C1 * (MetaCons "ISRequested" PrefixI False) (U1 *)))))

LagState

data LagState Source #

The state of the LAG.

  • Requested : The initial state of a LAG. The LAG stays in the requested state until the Letter of Authorization (LOA) is available.
  • Pending : The LAG has been approved, and is being initialized.
  • Available : The network link is established, and the LAG is ready for use.
  • Down : The network link is down.
  • Deleting : The LAG is in the process of being deleted.
  • Deleted : The LAG has been deleted.

Instances

Bounded LagState Source # 
Enum LagState Source # 
Eq LagState Source # 
Data LagState Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LagState -> c LagState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LagState #

toConstr :: LagState -> Constr #

dataTypeOf :: LagState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LagState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LagState) #

gmapT :: (forall b. Data b => b -> b) -> LagState -> LagState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LagState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LagState -> r #

gmapQ :: (forall d. Data d => d -> u) -> LagState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LagState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LagState -> m LagState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LagState -> m LagState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LagState -> m LagState #

Ord LagState Source # 
Read LagState Source # 
Show LagState Source # 
Generic LagState Source # 

Associated Types

type Rep LagState :: * -> * #

Methods

from :: LagState -> Rep LagState x #

to :: Rep LagState x -> LagState #

Hashable LagState Source # 

Methods

hashWithSalt :: Int -> LagState -> Int #

hash :: LagState -> Int #

FromJSON LagState Source # 
NFData LagState Source # 

Methods

rnf :: LagState -> () #

ToHeader LagState Source # 

Methods

toHeader :: HeaderName -> LagState -> [Header] #

ToQuery LagState Source # 
ToByteString LagState Source # 

Methods

toBS :: LagState -> ByteString #

FromText LagState Source # 
ToText LagState Source # 

Methods

toText :: LagState -> Text #

type Rep LagState Source # 
type Rep LagState = D1 * (MetaData "LagState" "Network.AWS.DirectConnect.Types.Sum" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) ((:+:) * ((:+:) * (C1 * (MetaCons "LSAvailable" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LSDeleted" PrefixI False) (U1 *)) (C1 * (MetaCons "LSDeleting" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "LSDown" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LSPending" PrefixI False) (U1 *)) (C1 * (MetaCons "LSRequested" PrefixI False) (U1 *)))))

LoaContentType

data LoaContentType Source #

A standard media type indicating the content type of the LOA-CFA document. Currently, the only supported value is "application/pdf".

Default: application/pdf

Constructors

ApplicationPdf 

Instances

Bounded LoaContentType Source # 
Enum LoaContentType Source # 
Eq LoaContentType Source # 
Data LoaContentType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LoaContentType -> c LoaContentType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LoaContentType #

toConstr :: LoaContentType -> Constr #

dataTypeOf :: LoaContentType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LoaContentType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LoaContentType) #

gmapT :: (forall b. Data b => b -> b) -> LoaContentType -> LoaContentType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LoaContentType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LoaContentType -> r #

gmapQ :: (forall d. Data d => d -> u) -> LoaContentType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LoaContentType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LoaContentType -> m LoaContentType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LoaContentType -> m LoaContentType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LoaContentType -> m LoaContentType #

Ord LoaContentType Source # 
Read LoaContentType Source # 
Show LoaContentType Source # 
Generic LoaContentType Source # 

Associated Types

type Rep LoaContentType :: * -> * #

Hashable LoaContentType Source # 
ToJSON LoaContentType Source # 
FromJSON LoaContentType Source # 
NFData LoaContentType Source # 

Methods

rnf :: LoaContentType -> () #

ToHeader LoaContentType Source # 
ToQuery LoaContentType Source # 
ToByteString LoaContentType Source # 
FromText LoaContentType Source # 
ToText LoaContentType Source # 
type Rep LoaContentType Source # 
type Rep LoaContentType = D1 * (MetaData "LoaContentType" "Network.AWS.DirectConnect.Types.Sum" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "ApplicationPdf" PrefixI False) (U1 *))

VirtualInterfaceState

data VirtualInterfaceState Source #

State of the virtual interface.

  • Confirming : The creation of the virtual interface is pending confirmation from the virtual interface owner. If the owner of the virtual interface is different from the owner of the connection on which it is provisioned, then the virtual interface will remain in this state until it is confirmed by the virtual interface owner.
  • Verifying : This state only applies to public virtual interfaces. Each public virtual interface needs validation before the virtual interface can be created.
  • Pending : A virtual interface is in this state from the time that it is created until the virtual interface is ready to forward traffic.
  • Available : A virtual interface that is able to forward traffic.
  • Down : A virtual interface that is BGP down.
  • Deleting : A virtual interface is in this state immediately after calling DeleteVirtualInterface until it can no longer forward traffic.
  • Deleted : A virtual interface that cannot forward traffic.
  • Rejected : The virtual interface owner has declined creation of the virtual interface. If a virtual interface in the Confirming state is deleted by the virtual interface owner, the virtual interface will enter the Rejected state.

Instances

Bounded VirtualInterfaceState Source # 
Enum VirtualInterfaceState Source # 
Eq VirtualInterfaceState Source # 
Data VirtualInterfaceState Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VirtualInterfaceState -> c VirtualInterfaceState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VirtualInterfaceState #

toConstr :: VirtualInterfaceState -> Constr #

dataTypeOf :: VirtualInterfaceState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VirtualInterfaceState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VirtualInterfaceState) #

gmapT :: (forall b. Data b => b -> b) -> VirtualInterfaceState -> VirtualInterfaceState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VirtualInterfaceState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VirtualInterfaceState -> r #

gmapQ :: (forall d. Data d => d -> u) -> VirtualInterfaceState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VirtualInterfaceState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VirtualInterfaceState -> m VirtualInterfaceState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VirtualInterfaceState -> m VirtualInterfaceState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VirtualInterfaceState -> m VirtualInterfaceState #

Ord VirtualInterfaceState Source # 
Read VirtualInterfaceState Source # 
Show VirtualInterfaceState Source # 
Generic VirtualInterfaceState Source # 
Hashable VirtualInterfaceState Source # 
FromJSON VirtualInterfaceState Source # 
NFData VirtualInterfaceState Source # 

Methods

rnf :: VirtualInterfaceState -> () #

ToHeader VirtualInterfaceState Source # 
ToQuery VirtualInterfaceState Source # 
ToByteString VirtualInterfaceState Source # 
FromText VirtualInterfaceState Source # 
ToText VirtualInterfaceState Source # 
type Rep VirtualInterfaceState Source # 
type Rep VirtualInterfaceState = D1 * (MetaData "VirtualInterfaceState" "Network.AWS.DirectConnect.Types.Sum" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "VISAvailable" PrefixI False) (U1 *)) (C1 * (MetaCons "VISConfirming" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "VISDeleted" PrefixI False) (U1 *)) (C1 * (MetaCons "VISDeleting" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "VISDown" PrefixI False) (U1 *)) (C1 * (MetaCons "VISPending" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "VISRejected" PrefixI False) (U1 *)) (C1 * (MetaCons "VISVerifying" PrefixI False) (U1 *)))))

BGPPeer

data BGPPeer Source #

A structure containing information about a BGP peer.

See: bgpPeer smart constructor.

Instances

Eq BGPPeer Source # 

Methods

(==) :: BGPPeer -> BGPPeer -> Bool #

(/=) :: BGPPeer -> BGPPeer -> Bool #

Data BGPPeer Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BGPPeer -> c BGPPeer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BGPPeer #

toConstr :: BGPPeer -> Constr #

dataTypeOf :: BGPPeer -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BGPPeer) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BGPPeer) #

gmapT :: (forall b. Data b => b -> b) -> BGPPeer -> BGPPeer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BGPPeer -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BGPPeer -> r #

gmapQ :: (forall d. Data d => d -> u) -> BGPPeer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BGPPeer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BGPPeer -> m BGPPeer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BGPPeer -> m BGPPeer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BGPPeer -> m BGPPeer #

Read BGPPeer Source # 
Show BGPPeer Source # 
Generic BGPPeer Source # 

Associated Types

type Rep BGPPeer :: * -> * #

Methods

from :: BGPPeer -> Rep BGPPeer x #

to :: Rep BGPPeer x -> BGPPeer #

Hashable BGPPeer Source # 

Methods

hashWithSalt :: Int -> BGPPeer -> Int #

hash :: BGPPeer -> Int #

FromJSON BGPPeer Source # 
NFData BGPPeer Source # 

Methods

rnf :: BGPPeer -> () #

type Rep BGPPeer Source # 

bgpPeer :: BGPPeer Source #

Creates a value of BGPPeer with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bpCustomerAddress :: Lens' BGPPeer (Maybe Text) Source #

Undocumented member.

bpAmazonAddress :: Lens' BGPPeer (Maybe Text) Source #

Undocumented member.

bpBgpStatus :: Lens' BGPPeer (Maybe BGPStatus) Source #

Undocumented member.

bpAsn :: Lens' BGPPeer (Maybe Int) Source #

Undocumented member.

bpAuthKey :: Lens' BGPPeer (Maybe Text) Source #

Undocumented member.

Connection

data Connection Source #

A connection represents the physical network connection between the AWS Direct Connect location and the customer.

See: connection smart constructor.

Instances

Eq Connection Source # 
Data Connection Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Connection -> c Connection #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Connection #

toConstr :: Connection -> Constr #

dataTypeOf :: Connection -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Connection) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Connection) #

gmapT :: (forall b. Data b => b -> b) -> Connection -> Connection #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Connection -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Connection -> r #

gmapQ :: (forall d. Data d => d -> u) -> Connection -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Connection -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Connection -> m Connection #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Connection -> m Connection #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Connection -> m Connection #

Read Connection Source # 
Show Connection Source # 
Generic Connection Source # 

Associated Types

type Rep Connection :: * -> * #

Hashable Connection Source # 
FromJSON Connection Source # 
NFData Connection Source # 

Methods

rnf :: Connection -> () #

type Rep Connection Source # 
type Rep Connection = D1 * (MetaData "Connection" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "Connection'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cLagId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cVlan") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_cLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cAwsDevice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cConnectionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cLoaIssueTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cPartnerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cConnectionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cBandwidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cOwnerAccount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cRegion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cConnectionState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ConnectionState))))))))

connection :: Connection Source #

Creates a value of Connection with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cLagId - Undocumented member.
  • cVlan - Undocumented member.
  • cLocation - Undocumented member.
  • cAwsDevice - The Direct Connection endpoint which the physical connection terminates on.
  • cConnectionId - Undocumented member.
  • cLoaIssueTime - The time of the most recent call to DescribeLoa for this connection.
  • cPartnerName - The name of the AWS Direct Connect service provider associated with the connection.
  • cConnectionName - Undocumented member.
  • cBandwidth - Bandwidth of the connection. Example: 1Gbps (for regular connections), or 500Mbps (for hosted connections) Default: None
  • cOwnerAccount - The AWS account that will own the new connection.
  • cRegion - Undocumented member.
  • cConnectionState - Undocumented member.

cLagId :: Lens' Connection (Maybe Text) Source #

Undocumented member.

cVlan :: Lens' Connection (Maybe Int) Source #

Undocumented member.

cLocation :: Lens' Connection (Maybe Text) Source #

Undocumented member.

cAwsDevice :: Lens' Connection (Maybe Text) Source #

The Direct Connection endpoint which the physical connection terminates on.

cConnectionId :: Lens' Connection (Maybe Text) Source #

Undocumented member.

cLoaIssueTime :: Lens' Connection (Maybe UTCTime) Source #

The time of the most recent call to DescribeLoa for this connection.

cPartnerName :: Lens' Connection (Maybe Text) Source #

The name of the AWS Direct Connect service provider associated with the connection.

cConnectionName :: Lens' Connection (Maybe Text) Source #

Undocumented member.

cBandwidth :: Lens' Connection (Maybe Text) Source #

Bandwidth of the connection. Example: 1Gbps (for regular connections), or 500Mbps (for hosted connections) Default: None

cOwnerAccount :: Lens' Connection (Maybe Text) Source #

The AWS account that will own the new connection.

cRegion :: Lens' Connection (Maybe Text) Source #

Undocumented member.

Connections

data Connections Source #

A structure containing a list of connections.

See: connections smart constructor.

Instances

Eq Connections Source # 
Data Connections Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Connections -> c Connections #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Connections #

toConstr :: Connections -> Constr #

dataTypeOf :: Connections -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Connections) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Connections) #

gmapT :: (forall b. Data b => b -> b) -> Connections -> Connections #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Connections -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Connections -> r #

gmapQ :: (forall d. Data d => d -> u) -> Connections -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Connections -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Connections -> m Connections #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Connections -> m Connections #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Connections -> m Connections #

Read Connections Source # 
Show Connections Source # 
Generic Connections Source # 

Associated Types

type Rep Connections :: * -> * #

Hashable Connections Source # 
FromJSON Connections Source # 
NFData Connections Source # 

Methods

rnf :: Connections -> () #

type Rep Connections Source # 
type Rep Connections = D1 * (MetaData "Connections" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" True) (C1 * (MetaCons "Connections'" PrefixI True) (S1 * (MetaSel (Just Symbol "_cConnections") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [Connection]))))

connections :: Connections Source #

Creates a value of Connections with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cConnections :: Lens' Connections [Connection] Source #

A list of connections.

DirectConnectGateway

data DirectConnectGateway Source #

A direct connect gateway is an intermediate object that enables you to connect virtual interfaces and virtual private gateways.

See: directConnectGateway smart constructor.

Instances

Eq DirectConnectGateway Source # 
Data DirectConnectGateway Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectConnectGateway -> c DirectConnectGateway #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectConnectGateway #

toConstr :: DirectConnectGateway -> Constr #

dataTypeOf :: DirectConnectGateway -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectConnectGateway) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectConnectGateway) #

gmapT :: (forall b. Data b => b -> b) -> DirectConnectGateway -> DirectConnectGateway #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGateway -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGateway -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectConnectGateway -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectConnectGateway -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectConnectGateway -> m DirectConnectGateway #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGateway -> m DirectConnectGateway #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGateway -> m DirectConnectGateway #

Read DirectConnectGateway Source # 
Show DirectConnectGateway Source # 
Generic DirectConnectGateway Source # 
Hashable DirectConnectGateway Source # 
FromJSON DirectConnectGateway Source # 
NFData DirectConnectGateway Source # 

Methods

rnf :: DirectConnectGateway -> () #

type Rep DirectConnectGateway Source # 
type Rep DirectConnectGateway = D1 * (MetaData "DirectConnectGateway" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "DirectConnectGateway'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dcgDirectConnectGatewayId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dcgStateChangeError") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dcgAmazonSideASN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dcgDirectConnectGatewayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dcgDirectConnectGatewayState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DirectConnectGatewayState))) (S1 * (MetaSel (Just Symbol "_dcgOwnerAccount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

directConnectGateway :: DirectConnectGateway Source #

Creates a value of DirectConnectGateway with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dcgAmazonSideASN :: Lens' DirectConnectGateway (Maybe Integer) Source #

The autonomous system number (ASN) for the Amazon side of the connection.

dcgOwnerAccount :: Lens' DirectConnectGateway (Maybe Text) Source #

The AWS account ID of the owner of the direct connect gateway.

DirectConnectGatewayAssociation

data DirectConnectGatewayAssociation Source #

The association between a direct connect gateway and virtual private gateway.

See: directConnectGatewayAssociation smart constructor.

Instances

Eq DirectConnectGatewayAssociation Source # 
Data DirectConnectGatewayAssociation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectConnectGatewayAssociation -> c DirectConnectGatewayAssociation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectConnectGatewayAssociation #

toConstr :: DirectConnectGatewayAssociation -> Constr #

dataTypeOf :: DirectConnectGatewayAssociation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectConnectGatewayAssociation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectConnectGatewayAssociation) #

gmapT :: (forall b. Data b => b -> b) -> DirectConnectGatewayAssociation -> DirectConnectGatewayAssociation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGatewayAssociation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGatewayAssociation -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectConnectGatewayAssociation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectConnectGatewayAssociation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAssociation -> m DirectConnectGatewayAssociation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAssociation -> m DirectConnectGatewayAssociation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAssociation -> m DirectConnectGatewayAssociation #

Read DirectConnectGatewayAssociation Source # 
Show DirectConnectGatewayAssociation Source # 
Generic DirectConnectGatewayAssociation Source # 
Hashable DirectConnectGatewayAssociation Source # 
FromJSON DirectConnectGatewayAssociation Source # 
NFData DirectConnectGatewayAssociation Source # 
type Rep DirectConnectGatewayAssociation Source # 
type Rep DirectConnectGatewayAssociation = D1 * (MetaData "DirectConnectGatewayAssociation" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "DirectConnectGatewayAssociation'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dcgaVirtualGatewayId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dcgaDirectConnectGatewayId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dcgaVirtualGatewayOwnerAccount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dcgaStateChangeError") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dcgaVirtualGatewayRegion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dcgaAssociationState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DirectConnectGatewayAssociationState)))))))

directConnectGatewayAssociation :: DirectConnectGatewayAssociation Source #

Creates a value of DirectConnectGatewayAssociation with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dcgaVirtualGatewayOwnerAccount :: Lens' DirectConnectGatewayAssociation (Maybe Text) Source #

The AWS account ID of the owner of the virtual private gateway.

DirectConnectGatewayAttachment

data DirectConnectGatewayAttachment Source #

The association between a direct connect gateway and virtual interface.

See: directConnectGatewayAttachment smart constructor.

Instances

Eq DirectConnectGatewayAttachment Source # 
Data DirectConnectGatewayAttachment Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectConnectGatewayAttachment -> c DirectConnectGatewayAttachment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectConnectGatewayAttachment #

toConstr :: DirectConnectGatewayAttachment -> Constr #

dataTypeOf :: DirectConnectGatewayAttachment -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectConnectGatewayAttachment) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectConnectGatewayAttachment) #

gmapT :: (forall b. Data b => b -> b) -> DirectConnectGatewayAttachment -> DirectConnectGatewayAttachment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGatewayAttachment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectConnectGatewayAttachment -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectConnectGatewayAttachment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectConnectGatewayAttachment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAttachment -> m DirectConnectGatewayAttachment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAttachment -> m DirectConnectGatewayAttachment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectConnectGatewayAttachment -> m DirectConnectGatewayAttachment #

Read DirectConnectGatewayAttachment Source # 
Show DirectConnectGatewayAttachment Source # 
Generic DirectConnectGatewayAttachment Source # 
Hashable DirectConnectGatewayAttachment Source # 
FromJSON DirectConnectGatewayAttachment Source # 
NFData DirectConnectGatewayAttachment Source # 
type Rep DirectConnectGatewayAttachment Source # 
type Rep DirectConnectGatewayAttachment = D1 * (MetaData "DirectConnectGatewayAttachment" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "DirectConnectGatewayAttachment'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dDirectConnectGatewayId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dAttachmentState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DirectConnectGatewayAttachmentState))) (S1 * (MetaSel (Just Symbol "_dStateChangeError") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dVirtualInterfaceRegion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dVirtualInterfaceOwnerAccount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dVirtualInterfaceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

directConnectGatewayAttachment :: DirectConnectGatewayAttachment Source #

Creates a value of DirectConnectGatewayAttachment with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dVirtualInterfaceOwnerAccount :: Lens' DirectConnectGatewayAttachment (Maybe Text) Source #

The AWS account ID of the owner of the virtual interface.

Interconnect

data Interconnect Source #

An interconnect is a connection that can host other connections.

Like a standard AWS Direct Connect connection, an interconnect represents the physical connection between an AWS Direct Connect partner's network and a specific Direct Connect location. An AWS Direct Connect partner who owns an interconnect can provision hosted connections on the interconnect for their end customers, thereby providing the end customers with connectivity to AWS services.

The resources of the interconnect, including bandwidth and VLAN numbers, are shared by all of the hosted connections on the interconnect, and the owner of the interconnect determines how these resources are assigned.

See: interconnect smart constructor.

Instances

Eq Interconnect Source # 
Data Interconnect Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Interconnect -> c Interconnect #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Interconnect #

toConstr :: Interconnect -> Constr #

dataTypeOf :: Interconnect -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Interconnect) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Interconnect) #

gmapT :: (forall b. Data b => b -> b) -> Interconnect -> Interconnect #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Interconnect -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Interconnect -> r #

gmapQ :: (forall d. Data d => d -> u) -> Interconnect -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Interconnect -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Interconnect -> m Interconnect #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Interconnect -> m Interconnect #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Interconnect -> m Interconnect #

Read Interconnect Source # 
Show Interconnect Source # 
Generic Interconnect Source # 

Associated Types

type Rep Interconnect :: * -> * #

Hashable Interconnect Source # 
FromJSON Interconnect Source # 
NFData Interconnect Source # 

Methods

rnf :: Interconnect -> () #

type Rep Interconnect Source # 

interconnect :: Interconnect Source #

Creates a value of Interconnect with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

iLagId :: Lens' Interconnect (Maybe Text) Source #

Undocumented member.

iLocation :: Lens' Interconnect (Maybe Text) Source #

Undocumented member.

iAwsDevice :: Lens' Interconnect (Maybe Text) Source #

The Direct Connection endpoint which the physical connection terminates on.

iLoaIssueTime :: Lens' Interconnect (Maybe UTCTime) Source #

The time of the most recent call to DescribeInterconnectLoa for this Interconnect.

iBandwidth :: Lens' Interconnect (Maybe Text) Source #

Undocumented member.

iRegion :: Lens' Interconnect (Maybe Text) Source #

Undocumented member.

Lag

data Lag Source #

Describes a link aggregation group (LAG). A LAG is a connection that uses the Link Aggregation Control Protocol (LACP) to logically aggregate a bundle of physical connections. Like an interconnect, it can host other connections. All connections in a LAG must terminate on the same physical AWS Direct Connect endpoint, and must be the same bandwidth.

See: lag smart constructor.

Instances

Eq Lag Source # 

Methods

(==) :: Lag -> Lag -> Bool #

(/=) :: Lag -> Lag -> Bool #

Data Lag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Lag -> c Lag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Lag #

toConstr :: Lag -> Constr #

dataTypeOf :: Lag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Lag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lag) #

gmapT :: (forall b. Data b => b -> b) -> Lag -> Lag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lag -> r #

gmapQ :: (forall d. Data d => d -> u) -> Lag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Lag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Lag -> m Lag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Lag -> m Lag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Lag -> m Lag #

Read Lag Source # 
Show Lag Source # 

Methods

showsPrec :: Int -> Lag -> ShowS #

show :: Lag -> String #

showList :: [Lag] -> ShowS #

Generic Lag Source # 

Associated Types

type Rep Lag :: * -> * #

Methods

from :: Lag -> Rep Lag x #

to :: Rep Lag x -> Lag #

Hashable Lag Source # 

Methods

hashWithSalt :: Int -> Lag -> Int #

hash :: Lag -> Int #

FromJSON Lag Source # 
NFData Lag Source # 

Methods

rnf :: Lag -> () #

type Rep Lag Source # 
type Rep Lag = D1 * (MetaData "Lag" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "Lag'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lagLagId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lagConnectionsBandwidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lagMinimumLinks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lagLagName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lagLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lagConnections") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Connection])))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lagAwsDevice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lagAllowsHostedConnections") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_lagNumberOfConnections") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lagLagState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LagState))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lagOwnerAccount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lagRegion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))))

lag :: Lag Source #

Creates a value of Lag with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • lagLagId - Undocumented member.
  • lagConnectionsBandwidth - The individual bandwidth of the physical connections bundled by the LAG. Available values: 1Gbps, 10Gbps
  • lagMinimumLinks - The minimum number of physical connections that must be operational for the LAG itself to be operational. If the number of operational connections drops below this setting, the LAG state changes to down . This value can help to ensure that a LAG is not overutilized if a significant number of its bundled connections go down.
  • lagLagName - The name of the LAG.
  • lagLocation - Undocumented member.
  • lagConnections - A list of connections bundled by this LAG.
  • lagAwsDevice - The AWS Direct Connection endpoint that hosts the LAG.
  • lagAllowsHostedConnections - Indicates whether the LAG can host other connections.
  • lagNumberOfConnections - The number of physical connections bundled by the LAG, up to a maximum of 10.
  • lagLagState - Undocumented member.
  • lagOwnerAccount - The owner of the LAG.
  • lagRegion - Undocumented member.

lagLagId :: Lens' Lag (Maybe Text) Source #

Undocumented member.

lagConnectionsBandwidth :: Lens' Lag (Maybe Text) Source #

The individual bandwidth of the physical connections bundled by the LAG. Available values: 1Gbps, 10Gbps

lagMinimumLinks :: Lens' Lag (Maybe Int) Source #

The minimum number of physical connections that must be operational for the LAG itself to be operational. If the number of operational connections drops below this setting, the LAG state changes to down . This value can help to ensure that a LAG is not overutilized if a significant number of its bundled connections go down.

lagLagName :: Lens' Lag (Maybe Text) Source #

The name of the LAG.

lagLocation :: Lens' Lag (Maybe Text) Source #

Undocumented member.

lagConnections :: Lens' Lag [Connection] Source #

A list of connections bundled by this LAG.

lagAwsDevice :: Lens' Lag (Maybe Text) Source #

The AWS Direct Connection endpoint that hosts the LAG.

lagAllowsHostedConnections :: Lens' Lag (Maybe Bool) Source #

Indicates whether the LAG can host other connections.

lagNumberOfConnections :: Lens' Lag (Maybe Int) Source #

The number of physical connections bundled by the LAG, up to a maximum of 10.

lagLagState :: Lens' Lag (Maybe LagState) Source #

Undocumented member.

lagOwnerAccount :: Lens' Lag (Maybe Text) Source #

The owner of the LAG.

lagRegion :: Lens' Lag (Maybe Text) Source #

Undocumented member.

Location

data Location Source #

An AWS Direct Connect location where connections and interconnects can be requested.

See: location smart constructor.

Instances

Eq Location Source # 
Data Location Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Location -> c Location #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Location #

toConstr :: Location -> Constr #

dataTypeOf :: Location -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Location) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Location) #

gmapT :: (forall b. Data b => b -> b) -> Location -> Location #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Location -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Location -> r #

gmapQ :: (forall d. Data d => d -> u) -> Location -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Location -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Location -> m Location #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Location -> m Location #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Location -> m Location #

Read Location Source # 
Show Location Source # 
Generic Location Source # 

Associated Types

type Rep Location :: * -> * #

Methods

from :: Location -> Rep Location x #

to :: Rep Location x -> Location #

Hashable Location Source # 

Methods

hashWithSalt :: Int -> Location -> Int #

hash :: Location -> Int #

FromJSON Location Source # 
NFData Location Source # 

Methods

rnf :: Location -> () #

type Rep Location Source # 
type Rep Location = D1 * (MetaData "Location" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "Location'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lLocationName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lLocationCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

location :: Location Source #

Creates a value of Location with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • lLocationName - The name of the AWS Direct Connect location. The name includes the colocation partner name and the physical site of the lit building.
  • lLocationCode - The code used to indicate the AWS Direct Connect location.

lLocationName :: Lens' Location (Maybe Text) Source #

The name of the AWS Direct Connect location. The name includes the colocation partner name and the physical site of the lit building.

lLocationCode :: Lens' Location (Maybe Text) Source #

The code used to indicate the AWS Direct Connect location.

NewBGPPeer

data NewBGPPeer Source #

A structure containing information about a new BGP peer.

See: newBGPPeer smart constructor.

Instances

Eq NewBGPPeer Source # 
Data NewBGPPeer Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewBGPPeer -> c NewBGPPeer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewBGPPeer #

toConstr :: NewBGPPeer -> Constr #

dataTypeOf :: NewBGPPeer -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NewBGPPeer) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewBGPPeer) #

gmapT :: (forall b. Data b => b -> b) -> NewBGPPeer -> NewBGPPeer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewBGPPeer -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewBGPPeer -> r #

gmapQ :: (forall d. Data d => d -> u) -> NewBGPPeer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NewBGPPeer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewBGPPeer -> m NewBGPPeer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewBGPPeer -> m NewBGPPeer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewBGPPeer -> m NewBGPPeer #

Read NewBGPPeer Source # 
Show NewBGPPeer Source # 
Generic NewBGPPeer Source # 

Associated Types

type Rep NewBGPPeer :: * -> * #

Hashable NewBGPPeer Source # 
ToJSON NewBGPPeer Source # 
NFData NewBGPPeer Source # 

Methods

rnf :: NewBGPPeer -> () #

type Rep NewBGPPeer Source # 
type Rep NewBGPPeer = D1 * (MetaData "NewBGPPeer" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "NewBGPPeer'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_nbpCustomerAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_nbpAmazonAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_nbpAddressFamily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AddressFamily))) ((:*:) * (S1 * (MetaSel (Just Symbol "_nbpAsn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_nbpAuthKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

newBGPPeer :: NewBGPPeer Source #

Creates a value of NewBGPPeer with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

nbpAsn :: Lens' NewBGPPeer (Maybe Int) Source #

Undocumented member.

nbpAuthKey :: Lens' NewBGPPeer (Maybe Text) Source #

Undocumented member.

NewPrivateVirtualInterface

data NewPrivateVirtualInterface Source #

A structure containing information about a new private virtual interface.

See: newPrivateVirtualInterface smart constructor.

Instances

Eq NewPrivateVirtualInterface Source # 
Data NewPrivateVirtualInterface Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewPrivateVirtualInterface -> c NewPrivateVirtualInterface #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewPrivateVirtualInterface #

toConstr :: NewPrivateVirtualInterface -> Constr #

dataTypeOf :: NewPrivateVirtualInterface -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NewPrivateVirtualInterface) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewPrivateVirtualInterface) #

gmapT :: (forall b. Data b => b -> b) -> NewPrivateVirtualInterface -> NewPrivateVirtualInterface #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewPrivateVirtualInterface -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewPrivateVirtualInterface -> r #

gmapQ :: (forall d. Data d => d -> u) -> NewPrivateVirtualInterface -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NewPrivateVirtualInterface -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewPrivateVirtualInterface -> m NewPrivateVirtualInterface #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewPrivateVirtualInterface -> m NewPrivateVirtualInterface #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewPrivateVirtualInterface -> m NewPrivateVirtualInterface #

Read NewPrivateVirtualInterface Source # 
Show NewPrivateVirtualInterface Source # 
Generic NewPrivateVirtualInterface Source # 
Hashable NewPrivateVirtualInterface Source # 
ToJSON NewPrivateVirtualInterface Source # 
NFData NewPrivateVirtualInterface Source # 
type Rep NewPrivateVirtualInterface Source # 
type Rep NewPrivateVirtualInterface = D1 * (MetaData "NewPrivateVirtualInterface" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "NewPrivateVirtualInterface'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_nVirtualGatewayId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_nCustomerAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_nAmazonAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_nAddressFamily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AddressFamily))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_nDirectConnectGatewayId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_nAuthKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_nVirtualInterfaceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "_nVlan") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "_nAsn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)))))))

newPrivateVirtualInterface Source #

Creates a value of NewPrivateVirtualInterface with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

NewPrivateVirtualInterfaceAllocation

data NewPrivateVirtualInterfaceAllocation Source #

A structure containing information about a private virtual interface that will be provisioned on a connection.

See: newPrivateVirtualInterfaceAllocation smart constructor.

Instances

Eq NewPrivateVirtualInterfaceAllocation Source # 
Data NewPrivateVirtualInterfaceAllocation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewPrivateVirtualInterfaceAllocation -> c NewPrivateVirtualInterfaceAllocation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewPrivateVirtualInterfaceAllocation #

toConstr :: NewPrivateVirtualInterfaceAllocation -> Constr #

dataTypeOf :: NewPrivateVirtualInterfaceAllocation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NewPrivateVirtualInterfaceAllocation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewPrivateVirtualInterfaceAllocation) #

gmapT :: (forall b. Data b => b -> b) -> NewPrivateVirtualInterfaceAllocation -> NewPrivateVirtualInterfaceAllocation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewPrivateVirtualInterfaceAllocation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewPrivateVirtualInterfaceAllocation -> r #

gmapQ :: (forall d. Data d => d -> u) -> NewPrivateVirtualInterfaceAllocation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NewPrivateVirtualInterfaceAllocation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewPrivateVirtualInterfaceAllocation -> m NewPrivateVirtualInterfaceAllocation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewPrivateVirtualInterfaceAllocation -> m NewPrivateVirtualInterfaceAllocation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewPrivateVirtualInterfaceAllocation -> m NewPrivateVirtualInterfaceAllocation #

Read NewPrivateVirtualInterfaceAllocation Source # 
Show NewPrivateVirtualInterfaceAllocation Source # 
Generic NewPrivateVirtualInterfaceAllocation Source # 
Hashable NewPrivateVirtualInterfaceAllocation Source # 
ToJSON NewPrivateVirtualInterfaceAllocation Source # 
NFData NewPrivateVirtualInterfaceAllocation Source # 
type Rep NewPrivateVirtualInterfaceAllocation Source # 
type Rep NewPrivateVirtualInterfaceAllocation = D1 * (MetaData "NewPrivateVirtualInterfaceAllocation" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "NewPrivateVirtualInterfaceAllocation'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_npviaCustomerAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_npviaAmazonAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_npviaAddressFamily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AddressFamily))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_npviaAuthKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_npviaVirtualInterfaceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_npviaVlan") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "_npviaAsn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int))))))

newPrivateVirtualInterfaceAllocation Source #

Creates a value of NewPrivateVirtualInterfaceAllocation with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

NewPublicVirtualInterface

data NewPublicVirtualInterface Source #

A structure containing information about a new public virtual interface.

See: newPublicVirtualInterface smart constructor.

Instances

Eq NewPublicVirtualInterface Source # 
Data NewPublicVirtualInterface Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewPublicVirtualInterface -> c NewPublicVirtualInterface #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewPublicVirtualInterface #

toConstr :: NewPublicVirtualInterface -> Constr #

dataTypeOf :: NewPublicVirtualInterface -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NewPublicVirtualInterface) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewPublicVirtualInterface) #

gmapT :: (forall b. Data b => b -> b) -> NewPublicVirtualInterface -> NewPublicVirtualInterface #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewPublicVirtualInterface -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewPublicVirtualInterface -> r #

gmapQ :: (forall d. Data d => d -> u) -> NewPublicVirtualInterface -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NewPublicVirtualInterface -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewPublicVirtualInterface -> m NewPublicVirtualInterface #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewPublicVirtualInterface -> m NewPublicVirtualInterface #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewPublicVirtualInterface -> m NewPublicVirtualInterface #

Read NewPublicVirtualInterface Source # 
Show NewPublicVirtualInterface Source # 
Generic NewPublicVirtualInterface Source # 
Hashable NewPublicVirtualInterface Source # 
ToJSON NewPublicVirtualInterface Source # 
NFData NewPublicVirtualInterface Source # 
type Rep NewPublicVirtualInterface Source # 
type Rep NewPublicVirtualInterface = D1 * (MetaData "NewPublicVirtualInterface" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "NewPublicVirtualInterface'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_npviRouteFilterPrefixes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [RouteFilterPrefix]))) (S1 * (MetaSel (Just Symbol "_npviCustomerAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_npviAmazonAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_npviAddressFamily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AddressFamily))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_npviAuthKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_npviVirtualInterfaceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_npviVlan") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "_npviAsn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int))))))

newPublicVirtualInterface Source #

Creates a value of NewPublicVirtualInterface with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

NewPublicVirtualInterfaceAllocation

data NewPublicVirtualInterfaceAllocation Source #

A structure containing information about a public virtual interface that will be provisioned on a connection.

See: newPublicVirtualInterfaceAllocation smart constructor.

Instances

Eq NewPublicVirtualInterfaceAllocation Source # 
Data NewPublicVirtualInterfaceAllocation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewPublicVirtualInterfaceAllocation -> c NewPublicVirtualInterfaceAllocation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewPublicVirtualInterfaceAllocation #

toConstr :: NewPublicVirtualInterfaceAllocation -> Constr #

dataTypeOf :: NewPublicVirtualInterfaceAllocation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NewPublicVirtualInterfaceAllocation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewPublicVirtualInterfaceAllocation) #

gmapT :: (forall b. Data b => b -> b) -> NewPublicVirtualInterfaceAllocation -> NewPublicVirtualInterfaceAllocation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewPublicVirtualInterfaceAllocation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewPublicVirtualInterfaceAllocation -> r #

gmapQ :: (forall d. Data d => d -> u) -> NewPublicVirtualInterfaceAllocation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NewPublicVirtualInterfaceAllocation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewPublicVirtualInterfaceAllocation -> m NewPublicVirtualInterfaceAllocation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewPublicVirtualInterfaceAllocation -> m NewPublicVirtualInterfaceAllocation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewPublicVirtualInterfaceAllocation -> m NewPublicVirtualInterfaceAllocation #

Read NewPublicVirtualInterfaceAllocation Source # 
Show NewPublicVirtualInterfaceAllocation Source # 
Generic NewPublicVirtualInterfaceAllocation Source # 
Hashable NewPublicVirtualInterfaceAllocation Source # 
ToJSON NewPublicVirtualInterfaceAllocation Source # 
NFData NewPublicVirtualInterfaceAllocation Source # 
type Rep NewPublicVirtualInterfaceAllocation Source # 
type Rep NewPublicVirtualInterfaceAllocation = D1 * (MetaData "NewPublicVirtualInterfaceAllocation" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "NewPublicVirtualInterfaceAllocation'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_newRouteFilterPrefixes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [RouteFilterPrefix]))) (S1 * (MetaSel (Just Symbol "_newCustomerAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_newAmazonAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_newAddressFamily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AddressFamily))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_newAuthKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_newVirtualInterfaceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_newVlan") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "_newAsn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int))))))

newPublicVirtualInterfaceAllocation Source #

Creates a value of NewPublicVirtualInterfaceAllocation with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ResourceTag

data ResourceTag Source #

The tags associated with a Direct Connect resource.

See: resourceTag smart constructor.

Instances

Eq ResourceTag Source # 
Data ResourceTag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResourceTag -> c ResourceTag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResourceTag #

toConstr :: ResourceTag -> Constr #

dataTypeOf :: ResourceTag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ResourceTag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResourceTag) #

gmapT :: (forall b. Data b => b -> b) -> ResourceTag -> ResourceTag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResourceTag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResourceTag -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResourceTag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResourceTag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResourceTag -> m ResourceTag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceTag -> m ResourceTag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceTag -> m ResourceTag #

Read ResourceTag Source # 
Show ResourceTag Source # 
Generic ResourceTag Source # 

Associated Types

type Rep ResourceTag :: * -> * #

Hashable ResourceTag Source # 
FromJSON ResourceTag Source # 
NFData ResourceTag Source # 

Methods

rnf :: ResourceTag -> () #

type Rep ResourceTag Source # 
type Rep ResourceTag = D1 * (MetaData "ResourceTag" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "ResourceTag'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rtResourceARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rtTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (List1 Tag))))))

resourceTag :: ResourceTag Source #

Creates a value of ResourceTag with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rtResourceARN - The Amazon Resource Name (ARN) of the Direct Connect resource.
  • rtTags - The tags.

rtResourceARN :: Lens' ResourceTag (Maybe Text) Source #

The Amazon Resource Name (ARN) of the Direct Connect resource.

RouteFilterPrefix

data RouteFilterPrefix Source #

A route filter prefix that the customer can advertise through Border Gateway Protocol (BGP) over a public virtual interface.

See: routeFilterPrefix smart constructor.

Instances

Eq RouteFilterPrefix Source # 
Data RouteFilterPrefix Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RouteFilterPrefix -> c RouteFilterPrefix #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RouteFilterPrefix #

toConstr :: RouteFilterPrefix -> Constr #

dataTypeOf :: RouteFilterPrefix -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RouteFilterPrefix) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RouteFilterPrefix) #

gmapT :: (forall b. Data b => b -> b) -> RouteFilterPrefix -> RouteFilterPrefix #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RouteFilterPrefix -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RouteFilterPrefix -> r #

gmapQ :: (forall d. Data d => d -> u) -> RouteFilterPrefix -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RouteFilterPrefix -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RouteFilterPrefix -> m RouteFilterPrefix #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RouteFilterPrefix -> m RouteFilterPrefix #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RouteFilterPrefix -> m RouteFilterPrefix #

Read RouteFilterPrefix Source # 
Show RouteFilterPrefix Source # 
Generic RouteFilterPrefix Source # 
Hashable RouteFilterPrefix Source # 
ToJSON RouteFilterPrefix Source # 
FromJSON RouteFilterPrefix Source # 
NFData RouteFilterPrefix Source # 

Methods

rnf :: RouteFilterPrefix -> () #

type Rep RouteFilterPrefix Source # 
type Rep RouteFilterPrefix = D1 * (MetaData "RouteFilterPrefix" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" True) (C1 * (MetaCons "RouteFilterPrefix'" PrefixI True) (S1 * (MetaSel (Just Symbol "_rfpCidr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))))

routeFilterPrefix :: RouteFilterPrefix Source #

Creates a value of RouteFilterPrefix with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rfpCidr - CIDR notation for the advertised route. Multiple routes are separated by commas. IPv6 CIDRs must be at least a 64 or shorter Example: 10.10.10.024,10.10.11.024,2001:db8::64

rfpCidr :: Lens' RouteFilterPrefix (Maybe Text) Source #

CIDR notation for the advertised route. Multiple routes are separated by commas. IPv6 CIDRs must be at least a 64 or shorter Example: 10.10.10.024,10.10.11.024,2001:db8::64

Tag

data Tag Source #

Information about a tag.

See: tag smart constructor.

Instances

Eq Tag Source # 

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Data Tag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tag -> c Tag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tag #

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Tag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag) #

gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

Read Tag Source # 
Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

ToJSON Tag Source # 
FromJSON Tag Source # 
NFData Tag Source # 

Methods

rnf :: Tag -> () #

type Rep Tag Source # 
type Rep Tag = D1 * (MetaData "Tag" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "Tag'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_tagValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tagKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

tag Source #

Arguments

:: Text

tagKey

-> Tag 

Creates a value of Tag with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tagValue :: Lens' Tag (Maybe Text) Source #

The value of the tag.

tagKey :: Lens' Tag Text Source #

The key of the tag.

VirtualGateway

data VirtualGateway Source #

You can create one or more AWS Direct Connect private virtual interfaces linking to your virtual private gateway.

Virtual private gateways can be managed using the Amazon Virtual Private Cloud (Amazon VPC) console or the Amazon EC2 CreateVpnGateway action .

See: virtualGateway smart constructor.

Instances

Eq VirtualGateway Source # 
Data VirtualGateway Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VirtualGateway -> c VirtualGateway #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VirtualGateway #

toConstr :: VirtualGateway -> Constr #

dataTypeOf :: VirtualGateway -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VirtualGateway) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VirtualGateway) #

gmapT :: (forall b. Data b => b -> b) -> VirtualGateway -> VirtualGateway #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VirtualGateway -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VirtualGateway -> r #

gmapQ :: (forall d. Data d => d -> u) -> VirtualGateway -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VirtualGateway -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VirtualGateway -> m VirtualGateway #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VirtualGateway -> m VirtualGateway #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VirtualGateway -> m VirtualGateway #

Read VirtualGateway Source # 
Show VirtualGateway Source # 
Generic VirtualGateway Source # 

Associated Types

type Rep VirtualGateway :: * -> * #

Hashable VirtualGateway Source # 
FromJSON VirtualGateway Source # 
NFData VirtualGateway Source # 

Methods

rnf :: VirtualGateway -> () #

type Rep VirtualGateway Source # 
type Rep VirtualGateway = D1 * (MetaData "VirtualGateway" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "VirtualGateway'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_vgVirtualGatewayId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_vgVirtualGatewayState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

virtualGateway :: VirtualGateway Source #

Creates a value of VirtualGateway with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

VirtualInterface

data VirtualInterface Source #

A virtual interface (VLAN) transmits the traffic between the AWS Direct Connect location and the customer.

See: virtualInterface smart constructor.

Instances

Eq VirtualInterface Source # 
Data VirtualInterface Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VirtualInterface -> c VirtualInterface #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VirtualInterface #

toConstr :: VirtualInterface -> Constr #

dataTypeOf :: VirtualInterface -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VirtualInterface) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VirtualInterface) #

gmapT :: (forall b. Data b => b -> b) -> VirtualInterface -> VirtualInterface #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VirtualInterface -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VirtualInterface -> r #

gmapQ :: (forall d. Data d => d -> u) -> VirtualInterface -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VirtualInterface -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VirtualInterface -> m VirtualInterface #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VirtualInterface -> m VirtualInterface #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VirtualInterface -> m VirtualInterface #

Read VirtualInterface Source # 
Show VirtualInterface Source # 
Generic VirtualInterface Source # 
Hashable VirtualInterface Source # 
FromJSON VirtualInterface Source # 
NFData VirtualInterface Source # 

Methods

rnf :: VirtualInterface -> () #

type Rep VirtualInterface Source # 
type Rep VirtualInterface = D1 * (MetaData "VirtualInterface" "Network.AWS.DirectConnect.Types.Product" "amazonka-directconnect-1.6.0-3Ds8OcMuONt5kWQC5zsRrM" False) (C1 * (MetaCons "VirtualInterface'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_viBgpPeers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [BGPPeer]))) (S1 * (MetaSel (Just Symbol "_viVirtualGatewayId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_viRouteFilterPrefixes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [RouteFilterPrefix]))) (S1 * (MetaSel (Just Symbol "_viCustomerAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_viVlan") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_viLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_viAmazonAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_viAddressFamily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AddressFamily))) (S1 * (MetaSel (Just Symbol "_viVirtualInterfaceState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe VirtualInterfaceState))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_viConnectionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_viDirectConnectGatewayId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_viAmazonSideASN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) ((:*:) * (S1 * (MetaSel (Just Symbol "_viVirtualInterfaceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_viAsn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_viAuthKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_viCustomerRouterConfig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_viOwnerAccount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_viVirtualInterfaceName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_viVirtualInterfaceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))))

virtualInterface :: VirtualInterface Source #

Creates a value of VirtualInterface with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

viBgpPeers :: Lens' VirtualInterface [BGPPeer] Source #

Undocumented member.

viVlan :: Lens' VirtualInterface (Maybe Int) Source #

Undocumented member.

viAmazonSideASN :: Lens' VirtualInterface (Maybe Integer) Source #

The autonomous system number (ASN) for the Amazon side of the connection.

viAsn :: Lens' VirtualInterface (Maybe Int) Source #

Undocumented member.

viAuthKey :: Lens' VirtualInterface (Maybe Text) Source #

Undocumented member.

viCustomerRouterConfig :: Lens' VirtualInterface (Maybe Text) Source #

Information for generating the customer router configuration.

viOwnerAccount :: Lens' VirtualInterface (Maybe Text) Source #

The AWS account that will own the new virtual interface.