{-# 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.AssociateMacSecKey
-- 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 a MAC Security (MACsec) Connection Key Name (CKN)\/
-- Connectivity Association Key (CAK) pair with an Direct Connect dedicated
-- connection.
--
-- You must supply either the @secretARN,@ or the CKN\/CAK (@ckn@ and
-- @cak@) pair in the request.
--
-- For information about MAC Security (MACsec) key considerations, see
-- <https://docs.aws.amazon.com/directconnect/latest/UserGuide/direct-connect-mac-sec-getting-started.html#mac-sec-key-consideration MACsec pre-shared CKN\/CAK key considerations>
-- in the /Direct Connect User Guide/.
module Amazonka.DirectConnect.AssociateMacSecKey
  ( -- * Creating a Request
    AssociateMacSecKey (..),
    newAssociateMacSecKey,

    -- * Request Lenses
    associateMacSecKey_cak,
    associateMacSecKey_ckn,
    associateMacSecKey_secretARN,
    associateMacSecKey_connectionId,

    -- * Destructuring the Response
    AssociateMacSecKeyResponse (..),
    newAssociateMacSecKeyResponse,

    -- * Response Lenses
    associateMacSecKeyResponse_connectionId,
    associateMacSecKeyResponse_macSecKeys,
    associateMacSecKeyResponse_httpStatus,
  )
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:/ 'newAssociateMacSecKey' smart constructor.
data AssociateMacSecKey = AssociateMacSecKey'
  { -- | The MAC Security (MACsec) CAK to associate with the dedicated
    -- connection.
    --
    -- You can create the CKN\/CAK pair using an industry standard tool.
    --
    -- The valid values are 64 hexadecimal characters (0-9, A-E).
    --
    -- If you use this request parameter, you must use the @ckn@ request
    -- parameter and not use the @secretARN@ request parameter.
    AssociateMacSecKey -> Maybe Text
cak :: Prelude.Maybe Prelude.Text,
    -- | The MAC Security (MACsec) CKN to associate with the dedicated
    -- connection.
    --
    -- You can create the CKN\/CAK pair using an industry standard tool.
    --
    -- The valid values are 64 hexadecimal characters (0-9, A-E).
    --
    -- If you use this request parameter, you must use the @cak@ request
    -- parameter and not use the @secretARN@ request parameter.
    AssociateMacSecKey -> Maybe Text
ckn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the MAC Security (MACsec) secret key
    -- to associate with the dedicated connection.
    --
    -- You can use DescribeConnections or DescribeLags to retrieve the MAC
    -- Security (MACsec) secret key.
    --
    -- If you use this request parameter, you do not use the @ckn@ and @cak@
    -- request parameters.
    AssociateMacSecKey -> Maybe Text
secretARN :: Prelude.Maybe Prelude.Text,
    -- | The ID of the dedicated connection (dxcon-xxxx), or the ID of the LAG
    -- (dxlag-xxxx).
    --
    -- You can use DescribeConnections or DescribeLags to retrieve connection
    -- ID.
    AssociateMacSecKey -> Text
connectionId :: Prelude.Text
  }
  deriving (AssociateMacSecKey -> AssociateMacSecKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateMacSecKey -> AssociateMacSecKey -> Bool
$c/= :: AssociateMacSecKey -> AssociateMacSecKey -> Bool
== :: AssociateMacSecKey -> AssociateMacSecKey -> Bool
$c== :: AssociateMacSecKey -> AssociateMacSecKey -> Bool
Prelude.Eq, ReadPrec [AssociateMacSecKey]
ReadPrec AssociateMacSecKey
Int -> ReadS AssociateMacSecKey
ReadS [AssociateMacSecKey]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateMacSecKey]
$creadListPrec :: ReadPrec [AssociateMacSecKey]
readPrec :: ReadPrec AssociateMacSecKey
$creadPrec :: ReadPrec AssociateMacSecKey
readList :: ReadS [AssociateMacSecKey]
$creadList :: ReadS [AssociateMacSecKey]
readsPrec :: Int -> ReadS AssociateMacSecKey
$creadsPrec :: Int -> ReadS AssociateMacSecKey
Prelude.Read, Int -> AssociateMacSecKey -> ShowS
[AssociateMacSecKey] -> ShowS
AssociateMacSecKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateMacSecKey] -> ShowS
$cshowList :: [AssociateMacSecKey] -> ShowS
show :: AssociateMacSecKey -> String
$cshow :: AssociateMacSecKey -> String
showsPrec :: Int -> AssociateMacSecKey -> ShowS
$cshowsPrec :: Int -> AssociateMacSecKey -> ShowS
Prelude.Show, forall x. Rep AssociateMacSecKey x -> AssociateMacSecKey
forall x. AssociateMacSecKey -> Rep AssociateMacSecKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssociateMacSecKey x -> AssociateMacSecKey
$cfrom :: forall x. AssociateMacSecKey -> Rep AssociateMacSecKey x
Prelude.Generic)

-- |
-- Create a value of 'AssociateMacSecKey' 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:
--
-- 'cak', 'associateMacSecKey_cak' - The MAC Security (MACsec) CAK to associate with the dedicated
-- connection.
--
-- You can create the CKN\/CAK pair using an industry standard tool.
--
-- The valid values are 64 hexadecimal characters (0-9, A-E).
--
-- If you use this request parameter, you must use the @ckn@ request
-- parameter and not use the @secretARN@ request parameter.
--
-- 'ckn', 'associateMacSecKey_ckn' - The MAC Security (MACsec) CKN to associate with the dedicated
-- connection.
--
-- You can create the CKN\/CAK pair using an industry standard tool.
--
-- The valid values are 64 hexadecimal characters (0-9, A-E).
--
-- If you use this request parameter, you must use the @cak@ request
-- parameter and not use the @secretARN@ request parameter.
--
-- 'secretARN', 'associateMacSecKey_secretARN' - The Amazon Resource Name (ARN) of the MAC Security (MACsec) secret key
-- to associate with the dedicated connection.
--
-- You can use DescribeConnections or DescribeLags to retrieve the MAC
-- Security (MACsec) secret key.
--
-- If you use this request parameter, you do not use the @ckn@ and @cak@
-- request parameters.
--
-- 'connectionId', 'associateMacSecKey_connectionId' - The ID of the dedicated connection (dxcon-xxxx), or the ID of the LAG
-- (dxlag-xxxx).
--
-- You can use DescribeConnections or DescribeLags to retrieve connection
-- ID.
newAssociateMacSecKey ::
  -- | 'connectionId'
  Prelude.Text ->
  AssociateMacSecKey
newAssociateMacSecKey :: Text -> AssociateMacSecKey
newAssociateMacSecKey Text
pConnectionId_ =
  AssociateMacSecKey'
    { $sel:cak:AssociateMacSecKey' :: Maybe Text
cak = forall a. Maybe a
Prelude.Nothing,
      $sel:ckn:AssociateMacSecKey' :: Maybe Text
ckn = forall a. Maybe a
Prelude.Nothing,
      $sel:secretARN:AssociateMacSecKey' :: Maybe Text
secretARN = forall a. Maybe a
Prelude.Nothing,
      $sel:connectionId:AssociateMacSecKey' :: Text
connectionId = Text
pConnectionId_
    }

-- | The MAC Security (MACsec) CAK to associate with the dedicated
-- connection.
--
-- You can create the CKN\/CAK pair using an industry standard tool.
--
-- The valid values are 64 hexadecimal characters (0-9, A-E).
--
-- If you use this request parameter, you must use the @ckn@ request
-- parameter and not use the @secretARN@ request parameter.
associateMacSecKey_cak :: Lens.Lens' AssociateMacSecKey (Prelude.Maybe Prelude.Text)
associateMacSecKey_cak :: Lens' AssociateMacSecKey (Maybe Text)
associateMacSecKey_cak = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateMacSecKey' {Maybe Text
cak :: Maybe Text
$sel:cak:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
cak} -> Maybe Text
cak) (\s :: AssociateMacSecKey
s@AssociateMacSecKey' {} Maybe Text
a -> AssociateMacSecKey
s {$sel:cak:AssociateMacSecKey' :: Maybe Text
cak = Maybe Text
a} :: AssociateMacSecKey)

-- | The MAC Security (MACsec) CKN to associate with the dedicated
-- connection.
--
-- You can create the CKN\/CAK pair using an industry standard tool.
--
-- The valid values are 64 hexadecimal characters (0-9, A-E).
--
-- If you use this request parameter, you must use the @cak@ request
-- parameter and not use the @secretARN@ request parameter.
associateMacSecKey_ckn :: Lens.Lens' AssociateMacSecKey (Prelude.Maybe Prelude.Text)
associateMacSecKey_ckn :: Lens' AssociateMacSecKey (Maybe Text)
associateMacSecKey_ckn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateMacSecKey' {Maybe Text
ckn :: Maybe Text
$sel:ckn:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
ckn} -> Maybe Text
ckn) (\s :: AssociateMacSecKey
s@AssociateMacSecKey' {} Maybe Text
a -> AssociateMacSecKey
s {$sel:ckn:AssociateMacSecKey' :: Maybe Text
ckn = Maybe Text
a} :: AssociateMacSecKey)

-- | The Amazon Resource Name (ARN) of the MAC Security (MACsec) secret key
-- to associate with the dedicated connection.
--
-- You can use DescribeConnections or DescribeLags to retrieve the MAC
-- Security (MACsec) secret key.
--
-- If you use this request parameter, you do not use the @ckn@ and @cak@
-- request parameters.
associateMacSecKey_secretARN :: Lens.Lens' AssociateMacSecKey (Prelude.Maybe Prelude.Text)
associateMacSecKey_secretARN :: Lens' AssociateMacSecKey (Maybe Text)
associateMacSecKey_secretARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateMacSecKey' {Maybe Text
secretARN :: Maybe Text
$sel:secretARN:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
secretARN} -> Maybe Text
secretARN) (\s :: AssociateMacSecKey
s@AssociateMacSecKey' {} Maybe Text
a -> AssociateMacSecKey
s {$sel:secretARN:AssociateMacSecKey' :: Maybe Text
secretARN = Maybe Text
a} :: AssociateMacSecKey)

-- | The ID of the dedicated connection (dxcon-xxxx), or the ID of the LAG
-- (dxlag-xxxx).
--
-- You can use DescribeConnections or DescribeLags to retrieve connection
-- ID.
associateMacSecKey_connectionId :: Lens.Lens' AssociateMacSecKey Prelude.Text
associateMacSecKey_connectionId :: Lens' AssociateMacSecKey Text
associateMacSecKey_connectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateMacSecKey' {Text
connectionId :: Text
$sel:connectionId:AssociateMacSecKey' :: AssociateMacSecKey -> Text
connectionId} -> Text
connectionId) (\s :: AssociateMacSecKey
s@AssociateMacSecKey' {} Text
a -> AssociateMacSecKey
s {$sel:connectionId:AssociateMacSecKey' :: Text
connectionId = Text
a} :: AssociateMacSecKey)

instance Core.AWSRequest AssociateMacSecKey where
  type
    AWSResponse AssociateMacSecKey =
      AssociateMacSecKeyResponse
  request :: (Service -> Service)
-> AssociateMacSecKey -> Request AssociateMacSecKey
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 AssociateMacSecKey
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssociateMacSecKey)))
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 ->
          Maybe Text
-> Maybe [MacSecKey] -> Int -> AssociateMacSecKeyResponse
AssociateMacSecKeyResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"connectionId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"macSecKeys" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable AssociateMacSecKey where
  hashWithSalt :: Int -> AssociateMacSecKey -> Int
hashWithSalt Int
_salt AssociateMacSecKey' {Maybe Text
Text
connectionId :: Text
secretARN :: Maybe Text
ckn :: Maybe Text
cak :: Maybe Text
$sel:connectionId:AssociateMacSecKey' :: AssociateMacSecKey -> Text
$sel:secretARN:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
$sel:ckn:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
$sel:cak:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cak
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ckn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
secretARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
connectionId

instance Prelude.NFData AssociateMacSecKey where
  rnf :: AssociateMacSecKey -> ()
rnf AssociateMacSecKey' {Maybe Text
Text
connectionId :: Text
secretARN :: Maybe Text
ckn :: Maybe Text
cak :: Maybe Text
$sel:connectionId:AssociateMacSecKey' :: AssociateMacSecKey -> Text
$sel:secretARN:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
$sel:ckn:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
$sel:cak:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cak
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ckn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
secretARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
connectionId

instance Data.ToHeaders AssociateMacSecKey where
  toHeaders :: AssociateMacSecKey -> 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.AssociateMacSecKey" ::
                          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 AssociateMacSecKey where
  toJSON :: AssociateMacSecKey -> Value
toJSON AssociateMacSecKey' {Maybe Text
Text
connectionId :: Text
secretARN :: Maybe Text
ckn :: Maybe Text
cak :: Maybe Text
$sel:connectionId:AssociateMacSecKey' :: AssociateMacSecKey -> Text
$sel:secretARN:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
$sel:ckn:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
$sel:cak:AssociateMacSecKey' :: AssociateMacSecKey -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"cak" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
cak,
            (Key
"ckn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
ckn,
            (Key
"secretARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
secretARN,
            forall a. a -> Maybe a
Prelude.Just (Key
"connectionId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
connectionId)
          ]
      )

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

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

-- | /See:/ 'newAssociateMacSecKeyResponse' smart constructor.
data AssociateMacSecKeyResponse = AssociateMacSecKeyResponse'
  { -- | The ID of the dedicated connection (dxcon-xxxx), or the ID of the LAG
    -- (dxlag-xxxx).
    AssociateMacSecKeyResponse -> Maybe Text
connectionId :: Prelude.Maybe Prelude.Text,
    -- | The MAC Security (MACsec) security keys associated with the dedicated
    -- connection.
    AssociateMacSecKeyResponse -> Maybe [MacSecKey]
macSecKeys :: Prelude.Maybe [MacSecKey],
    -- | The response's http status code.
    AssociateMacSecKeyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AssociateMacSecKeyResponse -> AssociateMacSecKeyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateMacSecKeyResponse -> AssociateMacSecKeyResponse -> Bool
$c/= :: AssociateMacSecKeyResponse -> AssociateMacSecKeyResponse -> Bool
== :: AssociateMacSecKeyResponse -> AssociateMacSecKeyResponse -> Bool
$c== :: AssociateMacSecKeyResponse -> AssociateMacSecKeyResponse -> Bool
Prelude.Eq, ReadPrec [AssociateMacSecKeyResponse]
ReadPrec AssociateMacSecKeyResponse
Int -> ReadS AssociateMacSecKeyResponse
ReadS [AssociateMacSecKeyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateMacSecKeyResponse]
$creadListPrec :: ReadPrec [AssociateMacSecKeyResponse]
readPrec :: ReadPrec AssociateMacSecKeyResponse
$creadPrec :: ReadPrec AssociateMacSecKeyResponse
readList :: ReadS [AssociateMacSecKeyResponse]
$creadList :: ReadS [AssociateMacSecKeyResponse]
readsPrec :: Int -> ReadS AssociateMacSecKeyResponse
$creadsPrec :: Int -> ReadS AssociateMacSecKeyResponse
Prelude.Read, Int -> AssociateMacSecKeyResponse -> ShowS
[AssociateMacSecKeyResponse] -> ShowS
AssociateMacSecKeyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateMacSecKeyResponse] -> ShowS
$cshowList :: [AssociateMacSecKeyResponse] -> ShowS
show :: AssociateMacSecKeyResponse -> String
$cshow :: AssociateMacSecKeyResponse -> String
showsPrec :: Int -> AssociateMacSecKeyResponse -> ShowS
$cshowsPrec :: Int -> AssociateMacSecKeyResponse -> ShowS
Prelude.Show, forall x.
Rep AssociateMacSecKeyResponse x -> AssociateMacSecKeyResponse
forall x.
AssociateMacSecKeyResponse -> Rep AssociateMacSecKeyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateMacSecKeyResponse x -> AssociateMacSecKeyResponse
$cfrom :: forall x.
AssociateMacSecKeyResponse -> Rep AssociateMacSecKeyResponse x
Prelude.Generic)

-- |
-- Create a value of 'AssociateMacSecKeyResponse' 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', 'associateMacSecKeyResponse_connectionId' - The ID of the dedicated connection (dxcon-xxxx), or the ID of the LAG
-- (dxlag-xxxx).
--
-- 'macSecKeys', 'associateMacSecKeyResponse_macSecKeys' - The MAC Security (MACsec) security keys associated with the dedicated
-- connection.
--
-- 'httpStatus', 'associateMacSecKeyResponse_httpStatus' - The response's http status code.
newAssociateMacSecKeyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AssociateMacSecKeyResponse
newAssociateMacSecKeyResponse :: Int -> AssociateMacSecKeyResponse
newAssociateMacSecKeyResponse Int
pHttpStatus_ =
  AssociateMacSecKeyResponse'
    { $sel:connectionId:AssociateMacSecKeyResponse' :: Maybe Text
connectionId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:macSecKeys:AssociateMacSecKeyResponse' :: Maybe [MacSecKey]
macSecKeys = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AssociateMacSecKeyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID of the dedicated connection (dxcon-xxxx), or the ID of the LAG
-- (dxlag-xxxx).
associateMacSecKeyResponse_connectionId :: Lens.Lens' AssociateMacSecKeyResponse (Prelude.Maybe Prelude.Text)
associateMacSecKeyResponse_connectionId :: Lens' AssociateMacSecKeyResponse (Maybe Text)
associateMacSecKeyResponse_connectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateMacSecKeyResponse' {Maybe Text
connectionId :: Maybe Text
$sel:connectionId:AssociateMacSecKeyResponse' :: AssociateMacSecKeyResponse -> Maybe Text
connectionId} -> Maybe Text
connectionId) (\s :: AssociateMacSecKeyResponse
s@AssociateMacSecKeyResponse' {} Maybe Text
a -> AssociateMacSecKeyResponse
s {$sel:connectionId:AssociateMacSecKeyResponse' :: Maybe Text
connectionId = Maybe Text
a} :: AssociateMacSecKeyResponse)

-- | The MAC Security (MACsec) security keys associated with the dedicated
-- connection.
associateMacSecKeyResponse_macSecKeys :: Lens.Lens' AssociateMacSecKeyResponse (Prelude.Maybe [MacSecKey])
associateMacSecKeyResponse_macSecKeys :: Lens' AssociateMacSecKeyResponse (Maybe [MacSecKey])
associateMacSecKeyResponse_macSecKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateMacSecKeyResponse' {Maybe [MacSecKey]
macSecKeys :: Maybe [MacSecKey]
$sel:macSecKeys:AssociateMacSecKeyResponse' :: AssociateMacSecKeyResponse -> Maybe [MacSecKey]
macSecKeys} -> Maybe [MacSecKey]
macSecKeys) (\s :: AssociateMacSecKeyResponse
s@AssociateMacSecKeyResponse' {} Maybe [MacSecKey]
a -> AssociateMacSecKeyResponse
s {$sel:macSecKeys:AssociateMacSecKeyResponse' :: Maybe [MacSecKey]
macSecKeys = Maybe [MacSecKey]
a} :: AssociateMacSecKeyResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The response's http status code.
associateMacSecKeyResponse_httpStatus :: Lens.Lens' AssociateMacSecKeyResponse Prelude.Int
associateMacSecKeyResponse_httpStatus :: Lens' AssociateMacSecKeyResponse Int
associateMacSecKeyResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateMacSecKeyResponse' {Int
httpStatus :: Int
$sel:httpStatus:AssociateMacSecKeyResponse' :: AssociateMacSecKeyResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AssociateMacSecKeyResponse
s@AssociateMacSecKeyResponse' {} Int
a -> AssociateMacSecKeyResponse
s {$sel:httpStatus:AssociateMacSecKeyResponse' :: Int
httpStatus = Int
a} :: AssociateMacSecKeyResponse)

instance Prelude.NFData AssociateMacSecKeyResponse where
  rnf :: AssociateMacSecKeyResponse -> ()
rnf AssociateMacSecKeyResponse' {Int
Maybe [MacSecKey]
Maybe Text
httpStatus :: Int
macSecKeys :: Maybe [MacSecKey]
connectionId :: Maybe Text
$sel:httpStatus:AssociateMacSecKeyResponse' :: AssociateMacSecKeyResponse -> Int
$sel:macSecKeys:AssociateMacSecKeyResponse' :: AssociateMacSecKeyResponse -> Maybe [MacSecKey]
$sel:connectionId:AssociateMacSecKeyResponse' :: AssociateMacSecKeyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [MacSecKey]
macSecKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus