{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.DirectConnect.AssociateHostedConnection
(
AssociateHostedConnection (..),
newAssociateHostedConnection,
associateHostedConnection_connectionId,
associateHostedConnection_parentConnectionId,
Connection (..),
newConnection,
connection_awsDevice,
connection_awsDeviceV2,
connection_awsLogicalDeviceId,
connection_bandwidth,
connection_connectionId,
connection_connectionName,
connection_connectionState,
connection_encryptionMode,
connection_hasLogicalRedundancy,
connection_jumboFrameCapable,
connection_lagId,
connection_loaIssueTime,
connection_location,
connection_macSecCapable,
connection_macSecKeys,
connection_ownerAccount,
connection_partnerName,
connection_portEncryptionStatus,
connection_providerName,
connection_region,
connection_tags,
connection_vlan,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DirectConnect.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data AssociateHostedConnection = AssociateHostedConnection'
{
AssociateHostedConnection -> Text
connectionId :: Prelude.Text,
AssociateHostedConnection -> Text
parentConnectionId :: Prelude.Text
}
deriving (AssociateHostedConnection -> AssociateHostedConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateHostedConnection -> AssociateHostedConnection -> Bool
$c/= :: AssociateHostedConnection -> AssociateHostedConnection -> Bool
== :: AssociateHostedConnection -> AssociateHostedConnection -> Bool
$c== :: AssociateHostedConnection -> AssociateHostedConnection -> Bool
Prelude.Eq, ReadPrec [AssociateHostedConnection]
ReadPrec AssociateHostedConnection
Int -> ReadS AssociateHostedConnection
ReadS [AssociateHostedConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateHostedConnection]
$creadListPrec :: ReadPrec [AssociateHostedConnection]
readPrec :: ReadPrec AssociateHostedConnection
$creadPrec :: ReadPrec AssociateHostedConnection
readList :: ReadS [AssociateHostedConnection]
$creadList :: ReadS [AssociateHostedConnection]
readsPrec :: Int -> ReadS AssociateHostedConnection
$creadsPrec :: Int -> ReadS AssociateHostedConnection
Prelude.Read, Int -> AssociateHostedConnection -> ShowS
[AssociateHostedConnection] -> ShowS
AssociateHostedConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateHostedConnection] -> ShowS
$cshowList :: [AssociateHostedConnection] -> ShowS
show :: AssociateHostedConnection -> String
$cshow :: AssociateHostedConnection -> String
showsPrec :: Int -> AssociateHostedConnection -> ShowS
$cshowsPrec :: Int -> AssociateHostedConnection -> ShowS
Prelude.Show, forall x.
Rep AssociateHostedConnection x -> AssociateHostedConnection
forall x.
AssociateHostedConnection -> Rep AssociateHostedConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateHostedConnection x -> AssociateHostedConnection
$cfrom :: forall x.
AssociateHostedConnection -> Rep AssociateHostedConnection x
Prelude.Generic)
newAssociateHostedConnection ::
Prelude.Text ->
Prelude.Text ->
AssociateHostedConnection
newAssociateHostedConnection :: Text -> Text -> AssociateHostedConnection
newAssociateHostedConnection
Text
pConnectionId_
Text
pParentConnectionId_ =
AssociateHostedConnection'
{ $sel:connectionId:AssociateHostedConnection' :: Text
connectionId =
Text
pConnectionId_,
$sel:parentConnectionId:AssociateHostedConnection' :: Text
parentConnectionId = Text
pParentConnectionId_
}
associateHostedConnection_connectionId :: Lens.Lens' AssociateHostedConnection Prelude.Text
associateHostedConnection_connectionId :: Lens' AssociateHostedConnection Text
associateHostedConnection_connectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateHostedConnection' {Text
connectionId :: Text
$sel:connectionId:AssociateHostedConnection' :: AssociateHostedConnection -> Text
connectionId} -> Text
connectionId) (\s :: AssociateHostedConnection
s@AssociateHostedConnection' {} Text
a -> AssociateHostedConnection
s {$sel:connectionId:AssociateHostedConnection' :: Text
connectionId = Text
a} :: AssociateHostedConnection)
associateHostedConnection_parentConnectionId :: Lens.Lens' AssociateHostedConnection Prelude.Text
associateHostedConnection_parentConnectionId :: Lens' AssociateHostedConnection Text
associateHostedConnection_parentConnectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateHostedConnection' {Text
parentConnectionId :: Text
$sel:parentConnectionId:AssociateHostedConnection' :: AssociateHostedConnection -> Text
parentConnectionId} -> Text
parentConnectionId) (\s :: AssociateHostedConnection
s@AssociateHostedConnection' {} Text
a -> AssociateHostedConnection
s {$sel:parentConnectionId:AssociateHostedConnection' :: Text
parentConnectionId = Text
a} :: AssociateHostedConnection)
instance Core.AWSRequest AssociateHostedConnection where
type
AWSResponse AssociateHostedConnection =
Connection
request :: (Service -> Service)
-> AssociateHostedConnection -> Request AssociateHostedConnection
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy AssociateHostedConnection
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse AssociateHostedConnection)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
(\Int
s ResponseHeaders
h Object
x -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
instance Prelude.Hashable AssociateHostedConnection where
hashWithSalt :: Int -> AssociateHostedConnection -> Int
hashWithSalt Int
_salt AssociateHostedConnection' {Text
parentConnectionId :: Text
connectionId :: Text
$sel:parentConnectionId:AssociateHostedConnection' :: AssociateHostedConnection -> Text
$sel:connectionId:AssociateHostedConnection' :: AssociateHostedConnection -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
connectionId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
parentConnectionId
instance Prelude.NFData AssociateHostedConnection where
rnf :: AssociateHostedConnection -> ()
rnf AssociateHostedConnection' {Text
parentConnectionId :: Text
connectionId :: Text
$sel:parentConnectionId:AssociateHostedConnection' :: AssociateHostedConnection -> Text
$sel:connectionId:AssociateHostedConnection' :: AssociateHostedConnection -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
connectionId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
parentConnectionId
instance Data.ToHeaders AssociateHostedConnection where
toHeaders :: AssociateHostedConnection -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"OvertureService.AssociateHostedConnection" ::
Prelude.ByteString
),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON AssociateHostedConnection where
toJSON :: AssociateHostedConnection -> Value
toJSON AssociateHostedConnection' {Text
parentConnectionId :: Text
connectionId :: Text
$sel:parentConnectionId:AssociateHostedConnection' :: AssociateHostedConnection -> Text
$sel:connectionId:AssociateHostedConnection' :: AssociateHostedConnection -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ forall a. a -> Maybe a
Prelude.Just (Key
"connectionId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
connectionId),
forall a. a -> Maybe a
Prelude.Just
(Key
"parentConnectionId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
parentConnectionId)
]
)
instance Data.ToPath AssociateHostedConnection where
toPath :: AssociateHostedConnection -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery AssociateHostedConnection where
toQuery :: AssociateHostedConnection -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty