{-# 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.NetworkManager.UpdateConnection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the information for an existing connection. To remove
-- information for any of the parameters, specify an empty string.
module Amazonka.NetworkManager.UpdateConnection
  ( -- * Creating a Request
    UpdateConnection (..),
    newUpdateConnection,

    -- * Request Lenses
    updateConnection_connectedLinkId,
    updateConnection_description,
    updateConnection_linkId,
    updateConnection_globalNetworkId,
    updateConnection_connectionId,

    -- * Destructuring the Response
    UpdateConnectionResponse (..),
    newUpdateConnectionResponse,

    -- * Response Lenses
    updateConnectionResponse_connection,
    updateConnectionResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.NetworkManager.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateConnection' smart constructor.
data UpdateConnection = UpdateConnection'
  { -- | The ID of the link for the second device in the connection.
    UpdateConnection -> Maybe Text
connectedLinkId :: Prelude.Maybe Prelude.Text,
    -- | A description of the connection.
    --
    -- Length Constraints: Maximum length of 256 characters.
    UpdateConnection -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The ID of the link for the first device in the connection.
    UpdateConnection -> Maybe Text
linkId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the global network.
    UpdateConnection -> Text
globalNetworkId :: Prelude.Text,
    -- | The ID of the connection.
    UpdateConnection -> Text
connectionId :: Prelude.Text
  }
  deriving (UpdateConnection -> UpdateConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConnection -> UpdateConnection -> Bool
$c/= :: UpdateConnection -> UpdateConnection -> Bool
== :: UpdateConnection -> UpdateConnection -> Bool
$c== :: UpdateConnection -> UpdateConnection -> Bool
Prelude.Eq, ReadPrec [UpdateConnection]
ReadPrec UpdateConnection
Int -> ReadS UpdateConnection
ReadS [UpdateConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConnection]
$creadListPrec :: ReadPrec [UpdateConnection]
readPrec :: ReadPrec UpdateConnection
$creadPrec :: ReadPrec UpdateConnection
readList :: ReadS [UpdateConnection]
$creadList :: ReadS [UpdateConnection]
readsPrec :: Int -> ReadS UpdateConnection
$creadsPrec :: Int -> ReadS UpdateConnection
Prelude.Read, Int -> UpdateConnection -> ShowS
[UpdateConnection] -> ShowS
UpdateConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConnection] -> ShowS
$cshowList :: [UpdateConnection] -> ShowS
show :: UpdateConnection -> String
$cshow :: UpdateConnection -> String
showsPrec :: Int -> UpdateConnection -> ShowS
$cshowsPrec :: Int -> UpdateConnection -> ShowS
Prelude.Show, forall x. Rep UpdateConnection x -> UpdateConnection
forall x. UpdateConnection -> Rep UpdateConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateConnection x -> UpdateConnection
$cfrom :: forall x. UpdateConnection -> Rep UpdateConnection x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConnection' 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:
--
-- 'connectedLinkId', 'updateConnection_connectedLinkId' - The ID of the link for the second device in the connection.
--
-- 'description', 'updateConnection_description' - A description of the connection.
--
-- Length Constraints: Maximum length of 256 characters.
--
-- 'linkId', 'updateConnection_linkId' - The ID of the link for the first device in the connection.
--
-- 'globalNetworkId', 'updateConnection_globalNetworkId' - The ID of the global network.
--
-- 'connectionId', 'updateConnection_connectionId' - The ID of the connection.
newUpdateConnection ::
  -- | 'globalNetworkId'
  Prelude.Text ->
  -- | 'connectionId'
  Prelude.Text ->
  UpdateConnection
newUpdateConnection :: Text -> Text -> UpdateConnection
newUpdateConnection Text
pGlobalNetworkId_ Text
pConnectionId_ =
  UpdateConnection'
    { $sel:connectedLinkId:UpdateConnection' :: Maybe Text
connectedLinkId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateConnection' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:linkId:UpdateConnection' :: Maybe Text
linkId = forall a. Maybe a
Prelude.Nothing,
      $sel:globalNetworkId:UpdateConnection' :: Text
globalNetworkId = Text
pGlobalNetworkId_,
      $sel:connectionId:UpdateConnection' :: Text
connectionId = Text
pConnectionId_
    }

-- | The ID of the link for the second device in the connection.
updateConnection_connectedLinkId :: Lens.Lens' UpdateConnection (Prelude.Maybe Prelude.Text)
updateConnection_connectedLinkId :: Lens' UpdateConnection (Maybe Text)
updateConnection_connectedLinkId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnection' {Maybe Text
connectedLinkId :: Maybe Text
$sel:connectedLinkId:UpdateConnection' :: UpdateConnection -> Maybe Text
connectedLinkId} -> Maybe Text
connectedLinkId) (\s :: UpdateConnection
s@UpdateConnection' {} Maybe Text
a -> UpdateConnection
s {$sel:connectedLinkId:UpdateConnection' :: Maybe Text
connectedLinkId = Maybe Text
a} :: UpdateConnection)

-- | A description of the connection.
--
-- Length Constraints: Maximum length of 256 characters.
updateConnection_description :: Lens.Lens' UpdateConnection (Prelude.Maybe Prelude.Text)
updateConnection_description :: Lens' UpdateConnection (Maybe Text)
updateConnection_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnection' {Maybe Text
description :: Maybe Text
$sel:description:UpdateConnection' :: UpdateConnection -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateConnection
s@UpdateConnection' {} Maybe Text
a -> UpdateConnection
s {$sel:description:UpdateConnection' :: Maybe Text
description = Maybe Text
a} :: UpdateConnection)

-- | The ID of the link for the first device in the connection.
updateConnection_linkId :: Lens.Lens' UpdateConnection (Prelude.Maybe Prelude.Text)
updateConnection_linkId :: Lens' UpdateConnection (Maybe Text)
updateConnection_linkId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnection' {Maybe Text
linkId :: Maybe Text
$sel:linkId:UpdateConnection' :: UpdateConnection -> Maybe Text
linkId} -> Maybe Text
linkId) (\s :: UpdateConnection
s@UpdateConnection' {} Maybe Text
a -> UpdateConnection
s {$sel:linkId:UpdateConnection' :: Maybe Text
linkId = Maybe Text
a} :: UpdateConnection)

-- | The ID of the global network.
updateConnection_globalNetworkId :: Lens.Lens' UpdateConnection Prelude.Text
updateConnection_globalNetworkId :: Lens' UpdateConnection Text
updateConnection_globalNetworkId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnection' {Text
globalNetworkId :: Text
$sel:globalNetworkId:UpdateConnection' :: UpdateConnection -> Text
globalNetworkId} -> Text
globalNetworkId) (\s :: UpdateConnection
s@UpdateConnection' {} Text
a -> UpdateConnection
s {$sel:globalNetworkId:UpdateConnection' :: Text
globalNetworkId = Text
a} :: UpdateConnection)

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

instance Core.AWSRequest UpdateConnection where
  type
    AWSResponse UpdateConnection =
      UpdateConnectionResponse
  request :: (Service -> Service)
-> UpdateConnection -> Request UpdateConnection
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateConnection
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateConnection)))
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 Connection -> Int -> UpdateConnectionResponse
UpdateConnectionResponse'
            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
"Connection")
            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 UpdateConnection where
  hashWithSalt :: Int -> UpdateConnection -> Int
hashWithSalt Int
_salt UpdateConnection' {Maybe Text
Text
connectionId :: Text
globalNetworkId :: Text
linkId :: Maybe Text
description :: Maybe Text
connectedLinkId :: Maybe Text
$sel:connectionId:UpdateConnection' :: UpdateConnection -> Text
$sel:globalNetworkId:UpdateConnection' :: UpdateConnection -> Text
$sel:linkId:UpdateConnection' :: UpdateConnection -> Maybe Text
$sel:description:UpdateConnection' :: UpdateConnection -> Maybe Text
$sel:connectedLinkId:UpdateConnection' :: UpdateConnection -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectedLinkId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
linkId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
globalNetworkId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
connectionId

instance Prelude.NFData UpdateConnection where
  rnf :: UpdateConnection -> ()
rnf UpdateConnection' {Maybe Text
Text
connectionId :: Text
globalNetworkId :: Text
linkId :: Maybe Text
description :: Maybe Text
connectedLinkId :: Maybe Text
$sel:connectionId:UpdateConnection' :: UpdateConnection -> Text
$sel:globalNetworkId:UpdateConnection' :: UpdateConnection -> Text
$sel:linkId:UpdateConnection' :: UpdateConnection -> Maybe Text
$sel:description:UpdateConnection' :: UpdateConnection -> Maybe Text
$sel:connectedLinkId:UpdateConnection' :: UpdateConnection -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectedLinkId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
linkId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
globalNetworkId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
connectionId

instance Data.ToHeaders UpdateConnection where
  toHeaders :: UpdateConnection -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateConnection where
  toJSON :: UpdateConnection -> Value
toJSON UpdateConnection' {Maybe Text
Text
connectionId :: Text
globalNetworkId :: Text
linkId :: Maybe Text
description :: Maybe Text
connectedLinkId :: Maybe Text
$sel:connectionId:UpdateConnection' :: UpdateConnection -> Text
$sel:globalNetworkId:UpdateConnection' :: UpdateConnection -> Text
$sel:linkId:UpdateConnection' :: UpdateConnection -> Maybe Text
$sel:description:UpdateConnection' :: UpdateConnection -> Maybe Text
$sel:connectedLinkId:UpdateConnection' :: UpdateConnection -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ConnectedLinkId" 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
connectedLinkId,
            (Key
"Description" 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
description,
            (Key
"LinkId" 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
linkId
          ]
      )

instance Data.ToPath UpdateConnection where
  toPath :: UpdateConnection -> ByteString
toPath UpdateConnection' {Maybe Text
Text
connectionId :: Text
globalNetworkId :: Text
linkId :: Maybe Text
description :: Maybe Text
connectedLinkId :: Maybe Text
$sel:connectionId:UpdateConnection' :: UpdateConnection -> Text
$sel:globalNetworkId:UpdateConnection' :: UpdateConnection -> Text
$sel:linkId:UpdateConnection' :: UpdateConnection -> Maybe Text
$sel:description:UpdateConnection' :: UpdateConnection -> Maybe Text
$sel:connectedLinkId:UpdateConnection' :: UpdateConnection -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/global-networks/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
globalNetworkId,
        ByteString
"/connections/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
connectionId
      ]

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

-- | /See:/ 'newUpdateConnectionResponse' smart constructor.
data UpdateConnectionResponse = UpdateConnectionResponse'
  { -- | Information about the connection.
    UpdateConnectionResponse -> Maybe Connection
connection :: Prelude.Maybe Connection,
    -- | The response's http status code.
    UpdateConnectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateConnectionResponse -> UpdateConnectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConnectionResponse -> UpdateConnectionResponse -> Bool
$c/= :: UpdateConnectionResponse -> UpdateConnectionResponse -> Bool
== :: UpdateConnectionResponse -> UpdateConnectionResponse -> Bool
$c== :: UpdateConnectionResponse -> UpdateConnectionResponse -> Bool
Prelude.Eq, ReadPrec [UpdateConnectionResponse]
ReadPrec UpdateConnectionResponse
Int -> ReadS UpdateConnectionResponse
ReadS [UpdateConnectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConnectionResponse]
$creadListPrec :: ReadPrec [UpdateConnectionResponse]
readPrec :: ReadPrec UpdateConnectionResponse
$creadPrec :: ReadPrec UpdateConnectionResponse
readList :: ReadS [UpdateConnectionResponse]
$creadList :: ReadS [UpdateConnectionResponse]
readsPrec :: Int -> ReadS UpdateConnectionResponse
$creadsPrec :: Int -> ReadS UpdateConnectionResponse
Prelude.Read, Int -> UpdateConnectionResponse -> ShowS
[UpdateConnectionResponse] -> ShowS
UpdateConnectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConnectionResponse] -> ShowS
$cshowList :: [UpdateConnectionResponse] -> ShowS
show :: UpdateConnectionResponse -> String
$cshow :: UpdateConnectionResponse -> String
showsPrec :: Int -> UpdateConnectionResponse -> ShowS
$cshowsPrec :: Int -> UpdateConnectionResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateConnectionResponse x -> UpdateConnectionResponse
forall x.
UpdateConnectionResponse -> Rep UpdateConnectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateConnectionResponse x -> UpdateConnectionResponse
$cfrom :: forall x.
UpdateConnectionResponse -> Rep UpdateConnectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConnectionResponse' 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:
--
-- 'connection', 'updateConnectionResponse_connection' - Information about the connection.
--
-- 'httpStatus', 'updateConnectionResponse_httpStatus' - The response's http status code.
newUpdateConnectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateConnectionResponse
newUpdateConnectionResponse :: Int -> UpdateConnectionResponse
newUpdateConnectionResponse Int
pHttpStatus_ =
  UpdateConnectionResponse'
    { $sel:connection:UpdateConnectionResponse' :: Maybe Connection
connection =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateConnectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the connection.
updateConnectionResponse_connection :: Lens.Lens' UpdateConnectionResponse (Prelude.Maybe Connection)
updateConnectionResponse_connection :: Lens' UpdateConnectionResponse (Maybe Connection)
updateConnectionResponse_connection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnectionResponse' {Maybe Connection
connection :: Maybe Connection
$sel:connection:UpdateConnectionResponse' :: UpdateConnectionResponse -> Maybe Connection
connection} -> Maybe Connection
connection) (\s :: UpdateConnectionResponse
s@UpdateConnectionResponse' {} Maybe Connection
a -> UpdateConnectionResponse
s {$sel:connection:UpdateConnectionResponse' :: Maybe Connection
connection = Maybe Connection
a} :: UpdateConnectionResponse)

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

instance Prelude.NFData UpdateConnectionResponse where
  rnf :: UpdateConnectionResponse -> ()
rnf UpdateConnectionResponse' {Int
Maybe Connection
httpStatus :: Int
connection :: Maybe Connection
$sel:httpStatus:UpdateConnectionResponse' :: UpdateConnectionResponse -> Int
$sel:connection:UpdateConnectionResponse' :: UpdateConnectionResponse -> Maybe Connection
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Connection
connection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus