{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.DirectConnect.AssociateConnectionWithLag
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Associates an existing connection with a link aggregation group (LAG).
-- The connection is interrupted and re-established as a member of the LAG
-- (connectivity to Amazon Web Services is interrupted). The connection
-- must be hosted on the same Direct Connect endpoint as the LAG, and its
-- bandwidth must match the bandwidth for the LAG. You can re-associate a
-- connection that\'s currently associated with a different LAG; however,
-- if removing the connection would cause the original LAG to fall below
-- its setting for minimum number of operational connections, the request
-- fails.
--
-- Any virtual interfaces that are directly associated with the connection
-- are automatically re-associated with the LAG. If the connection was
-- originally associated with a different LAG, the virtual interfaces
-- remain associated with the original LAG.
--
-- For interconnects, any hosted connections are automatically
-- re-associated with the LAG. If the interconnect was originally
-- associated with a different LAG, the hosted connections remain
-- associated with the original LAG.
module Amazonka.DirectConnect.AssociateConnectionWithLag
  ( -- * Creating a Request
    AssociateConnectionWithLag (..),
    newAssociateConnectionWithLag,

    -- * Request Lenses
    associateConnectionWithLag_connectionId,
    associateConnectionWithLag_lagId,

    -- * Destructuring the Response
    Connection (..),
    newConnection,

    -- * Response Lenses
    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

-- | /See:/ 'newAssociateConnectionWithLag' smart constructor.
data AssociateConnectionWithLag = AssociateConnectionWithLag'
  { -- | The ID of the connection.
    AssociateConnectionWithLag -> Text
connectionId :: Prelude.Text,
    -- | The ID of the LAG with which to associate the connection.
    AssociateConnectionWithLag -> Text
lagId :: Prelude.Text
  }
  deriving (AssociateConnectionWithLag -> AssociateConnectionWithLag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateConnectionWithLag -> AssociateConnectionWithLag -> Bool
$c/= :: AssociateConnectionWithLag -> AssociateConnectionWithLag -> Bool
== :: AssociateConnectionWithLag -> AssociateConnectionWithLag -> Bool
$c== :: AssociateConnectionWithLag -> AssociateConnectionWithLag -> Bool
Prelude.Eq, ReadPrec [AssociateConnectionWithLag]
ReadPrec AssociateConnectionWithLag
Int -> ReadS AssociateConnectionWithLag
ReadS [AssociateConnectionWithLag]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateConnectionWithLag]
$creadListPrec :: ReadPrec [AssociateConnectionWithLag]
readPrec :: ReadPrec AssociateConnectionWithLag
$creadPrec :: ReadPrec AssociateConnectionWithLag
readList :: ReadS [AssociateConnectionWithLag]
$creadList :: ReadS [AssociateConnectionWithLag]
readsPrec :: Int -> ReadS AssociateConnectionWithLag
$creadsPrec :: Int -> ReadS AssociateConnectionWithLag
Prelude.Read, Int -> AssociateConnectionWithLag -> ShowS
[AssociateConnectionWithLag] -> ShowS
AssociateConnectionWithLag -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateConnectionWithLag] -> ShowS
$cshowList :: [AssociateConnectionWithLag] -> ShowS
show :: AssociateConnectionWithLag -> String
$cshow :: AssociateConnectionWithLag -> String
showsPrec :: Int -> AssociateConnectionWithLag -> ShowS
$cshowsPrec :: Int -> AssociateConnectionWithLag -> ShowS
Prelude.Show, forall x.
Rep AssociateConnectionWithLag x -> AssociateConnectionWithLag
forall x.
AssociateConnectionWithLag -> Rep AssociateConnectionWithLag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateConnectionWithLag x -> AssociateConnectionWithLag
$cfrom :: forall x.
AssociateConnectionWithLag -> Rep AssociateConnectionWithLag x
Prelude.Generic)

-- |
-- Create a value of 'AssociateConnectionWithLag' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'connectionId', 'associateConnectionWithLag_connectionId' - The ID of the connection.
--
-- 'lagId', 'associateConnectionWithLag_lagId' - The ID of the LAG with which to associate the connection.
newAssociateConnectionWithLag ::
  -- | 'connectionId'
  Prelude.Text ->
  -- | 'lagId'
  Prelude.Text ->
  AssociateConnectionWithLag
newAssociateConnectionWithLag :: Text -> Text -> AssociateConnectionWithLag
newAssociateConnectionWithLag Text
pConnectionId_ Text
pLagId_ =
  AssociateConnectionWithLag'
    { $sel:connectionId:AssociateConnectionWithLag' :: Text
connectionId =
        Text
pConnectionId_,
      $sel:lagId:AssociateConnectionWithLag' :: Text
lagId = Text
pLagId_
    }

-- | The ID of the connection.
associateConnectionWithLag_connectionId :: Lens.Lens' AssociateConnectionWithLag Prelude.Text
associateConnectionWithLag_connectionId :: Lens' AssociateConnectionWithLag Text
associateConnectionWithLag_connectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateConnectionWithLag' {Text
connectionId :: Text
$sel:connectionId:AssociateConnectionWithLag' :: AssociateConnectionWithLag -> Text
connectionId} -> Text
connectionId) (\s :: AssociateConnectionWithLag
s@AssociateConnectionWithLag' {} Text
a -> AssociateConnectionWithLag
s {$sel:connectionId:AssociateConnectionWithLag' :: Text
connectionId = Text
a} :: AssociateConnectionWithLag)

-- | The ID of the LAG with which to associate the connection.
associateConnectionWithLag_lagId :: Lens.Lens' AssociateConnectionWithLag Prelude.Text
associateConnectionWithLag_lagId :: Lens' AssociateConnectionWithLag Text
associateConnectionWithLag_lagId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateConnectionWithLag' {Text
lagId :: Text
$sel:lagId:AssociateConnectionWithLag' :: AssociateConnectionWithLag -> Text
lagId} -> Text
lagId) (\s :: AssociateConnectionWithLag
s@AssociateConnectionWithLag' {} Text
a -> AssociateConnectionWithLag
s {$sel:lagId:AssociateConnectionWithLag' :: Text
lagId = Text
a} :: AssociateConnectionWithLag)

instance Core.AWSRequest AssociateConnectionWithLag where
  type
    AWSResponse AssociateConnectionWithLag =
      Connection
  request :: (Service -> Service)
-> AssociateConnectionWithLag -> Request AssociateConnectionWithLag
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 AssociateConnectionWithLag
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssociateConnectionWithLag)))
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 AssociateConnectionWithLag where
  hashWithSalt :: Int -> AssociateConnectionWithLag -> Int
hashWithSalt Int
_salt AssociateConnectionWithLag' {Text
lagId :: Text
connectionId :: Text
$sel:lagId:AssociateConnectionWithLag' :: AssociateConnectionWithLag -> Text
$sel:connectionId:AssociateConnectionWithLag' :: AssociateConnectionWithLag -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
connectionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
lagId

instance Prelude.NFData AssociateConnectionWithLag where
  rnf :: AssociateConnectionWithLag -> ()
rnf AssociateConnectionWithLag' {Text
lagId :: Text
connectionId :: Text
$sel:lagId:AssociateConnectionWithLag' :: AssociateConnectionWithLag -> Text
$sel:connectionId:AssociateConnectionWithLag' :: AssociateConnectionWithLag -> 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
lagId

instance Data.ToHeaders AssociateConnectionWithLag where
  toHeaders :: AssociateConnectionWithLag -> 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.AssociateConnectionWithLag" ::
                          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 AssociateConnectionWithLag where
  toJSON :: AssociateConnectionWithLag -> Value
toJSON AssociateConnectionWithLag' {Text
lagId :: Text
connectionId :: Text
$sel:lagId:AssociateConnectionWithLag' :: AssociateConnectionWithLag -> Text
$sel:connectionId:AssociateConnectionWithLag' :: AssociateConnectionWithLag -> 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
"lagId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
lagId)
          ]
      )

instance Data.ToPath AssociateConnectionWithLag where
  toPath :: AssociateConnectionWithLag -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery AssociateConnectionWithLag where
  toQuery :: AssociateConnectionWithLag -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty