{-# 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.GreengrassV2.UpdateConnectivityInfo
-- 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 connectivity information for a Greengrass core device.
--
-- Connectivity information includes endpoints and ports where client
-- devices can connect to an MQTT broker on the core device. When a client
-- device calls the
-- <https://docs.aws.amazon.com/greengrass/v2/developerguide/greengrass-discover-api.html IoT Greengrass discovery API>,
-- IoT Greengrass returns connectivity information for all of the core
-- devices where the client device can connect. For more information, see
-- <https://docs.aws.amazon.com/greengrass/v2/developerguide/connect-client-devices.html Connect client devices to core devices>
-- in the /IoT Greengrass Version 2 Developer Guide/.
module Amazonka.GreengrassV2.UpdateConnectivityInfo
  ( -- * Creating a Request
    UpdateConnectivityInfo (..),
    newUpdateConnectivityInfo,

    -- * Request Lenses
    updateConnectivityInfo_thingName,
    updateConnectivityInfo_connectivityInfo,

    -- * Destructuring the Response
    UpdateConnectivityInfoResponse (..),
    newUpdateConnectivityInfoResponse,

    -- * Response Lenses
    updateConnectivityInfoResponse_message,
    updateConnectivityInfoResponse_version,
    updateConnectivityInfoResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateConnectivityInfo' smart constructor.
data UpdateConnectivityInfo = UpdateConnectivityInfo'
  { -- | The name of the core device. This is also the name of the IoT thing.
    UpdateConnectivityInfo -> Text
thingName :: Prelude.Text,
    -- | The connectivity information for the core device.
    UpdateConnectivityInfo -> [ConnectivityInfo]
connectivityInfo :: [ConnectivityInfo]
  }
  deriving (UpdateConnectivityInfo -> UpdateConnectivityInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConnectivityInfo -> UpdateConnectivityInfo -> Bool
$c/= :: UpdateConnectivityInfo -> UpdateConnectivityInfo -> Bool
== :: UpdateConnectivityInfo -> UpdateConnectivityInfo -> Bool
$c== :: UpdateConnectivityInfo -> UpdateConnectivityInfo -> Bool
Prelude.Eq, ReadPrec [UpdateConnectivityInfo]
ReadPrec UpdateConnectivityInfo
Int -> ReadS UpdateConnectivityInfo
ReadS [UpdateConnectivityInfo]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConnectivityInfo]
$creadListPrec :: ReadPrec [UpdateConnectivityInfo]
readPrec :: ReadPrec UpdateConnectivityInfo
$creadPrec :: ReadPrec UpdateConnectivityInfo
readList :: ReadS [UpdateConnectivityInfo]
$creadList :: ReadS [UpdateConnectivityInfo]
readsPrec :: Int -> ReadS UpdateConnectivityInfo
$creadsPrec :: Int -> ReadS UpdateConnectivityInfo
Prelude.Read, Int -> UpdateConnectivityInfo -> ShowS
[UpdateConnectivityInfo] -> ShowS
UpdateConnectivityInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConnectivityInfo] -> ShowS
$cshowList :: [UpdateConnectivityInfo] -> ShowS
show :: UpdateConnectivityInfo -> String
$cshow :: UpdateConnectivityInfo -> String
showsPrec :: Int -> UpdateConnectivityInfo -> ShowS
$cshowsPrec :: Int -> UpdateConnectivityInfo -> ShowS
Prelude.Show, forall x. Rep UpdateConnectivityInfo x -> UpdateConnectivityInfo
forall x. UpdateConnectivityInfo -> Rep UpdateConnectivityInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateConnectivityInfo x -> UpdateConnectivityInfo
$cfrom :: forall x. UpdateConnectivityInfo -> Rep UpdateConnectivityInfo x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConnectivityInfo' 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:
--
-- 'thingName', 'updateConnectivityInfo_thingName' - The name of the core device. This is also the name of the IoT thing.
--
-- 'connectivityInfo', 'updateConnectivityInfo_connectivityInfo' - The connectivity information for the core device.
newUpdateConnectivityInfo ::
  -- | 'thingName'
  Prelude.Text ->
  UpdateConnectivityInfo
newUpdateConnectivityInfo :: Text -> UpdateConnectivityInfo
newUpdateConnectivityInfo Text
pThingName_ =
  UpdateConnectivityInfo'
    { $sel:thingName:UpdateConnectivityInfo' :: Text
thingName = Text
pThingName_,
      $sel:connectivityInfo:UpdateConnectivityInfo' :: [ConnectivityInfo]
connectivityInfo = forall a. Monoid a => a
Prelude.mempty
    }

-- | The name of the core device. This is also the name of the IoT thing.
updateConnectivityInfo_thingName :: Lens.Lens' UpdateConnectivityInfo Prelude.Text
updateConnectivityInfo_thingName :: Lens' UpdateConnectivityInfo Text
updateConnectivityInfo_thingName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnectivityInfo' {Text
thingName :: Text
$sel:thingName:UpdateConnectivityInfo' :: UpdateConnectivityInfo -> Text
thingName} -> Text
thingName) (\s :: UpdateConnectivityInfo
s@UpdateConnectivityInfo' {} Text
a -> UpdateConnectivityInfo
s {$sel:thingName:UpdateConnectivityInfo' :: Text
thingName = Text
a} :: UpdateConnectivityInfo)

-- | The connectivity information for the core device.
updateConnectivityInfo_connectivityInfo :: Lens.Lens' UpdateConnectivityInfo [ConnectivityInfo]
updateConnectivityInfo_connectivityInfo :: Lens' UpdateConnectivityInfo [ConnectivityInfo]
updateConnectivityInfo_connectivityInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnectivityInfo' {[ConnectivityInfo]
connectivityInfo :: [ConnectivityInfo]
$sel:connectivityInfo:UpdateConnectivityInfo' :: UpdateConnectivityInfo -> [ConnectivityInfo]
connectivityInfo} -> [ConnectivityInfo]
connectivityInfo) (\s :: UpdateConnectivityInfo
s@UpdateConnectivityInfo' {} [ConnectivityInfo]
a -> UpdateConnectivityInfo
s {$sel:connectivityInfo:UpdateConnectivityInfo' :: [ConnectivityInfo]
connectivityInfo = [ConnectivityInfo]
a} :: UpdateConnectivityInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest UpdateConnectivityInfo where
  type
    AWSResponse UpdateConnectivityInfo =
      UpdateConnectivityInfoResponse
  request :: (Service -> Service)
-> UpdateConnectivityInfo -> Request UpdateConnectivityInfo
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateConnectivityInfo
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateConnectivityInfo)))
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 Text -> Int -> UpdateConnectivityInfoResponse
UpdateConnectivityInfoResponse'
            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
"Message")
            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
"Version")
            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 UpdateConnectivityInfo where
  hashWithSalt :: Int -> UpdateConnectivityInfo -> Int
hashWithSalt Int
_salt UpdateConnectivityInfo' {[ConnectivityInfo]
Text
connectivityInfo :: [ConnectivityInfo]
thingName :: Text
$sel:connectivityInfo:UpdateConnectivityInfo' :: UpdateConnectivityInfo -> [ConnectivityInfo]
$sel:thingName:UpdateConnectivityInfo' :: UpdateConnectivityInfo -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
thingName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [ConnectivityInfo]
connectivityInfo

instance Prelude.NFData UpdateConnectivityInfo where
  rnf :: UpdateConnectivityInfo -> ()
rnf UpdateConnectivityInfo' {[ConnectivityInfo]
Text
connectivityInfo :: [ConnectivityInfo]
thingName :: Text
$sel:connectivityInfo:UpdateConnectivityInfo' :: UpdateConnectivityInfo -> [ConnectivityInfo]
$sel:thingName:UpdateConnectivityInfo' :: UpdateConnectivityInfo -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
thingName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [ConnectivityInfo]
connectivityInfo

instance Data.ToHeaders UpdateConnectivityInfo where
  toHeaders :: UpdateConnectivityInfo -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON UpdateConnectivityInfo where
  toJSON :: UpdateConnectivityInfo -> Value
toJSON UpdateConnectivityInfo' {[ConnectivityInfo]
Text
connectivityInfo :: [ConnectivityInfo]
thingName :: Text
$sel:connectivityInfo:UpdateConnectivityInfo' :: UpdateConnectivityInfo -> [ConnectivityInfo]
$sel:thingName:UpdateConnectivityInfo' :: UpdateConnectivityInfo -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"ConnectivityInfo" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [ConnectivityInfo]
connectivityInfo)
          ]
      )

instance Data.ToPath UpdateConnectivityInfo where
  toPath :: UpdateConnectivityInfo -> ByteString
toPath UpdateConnectivityInfo' {[ConnectivityInfo]
Text
connectivityInfo :: [ConnectivityInfo]
thingName :: Text
$sel:connectivityInfo:UpdateConnectivityInfo' :: UpdateConnectivityInfo -> [ConnectivityInfo]
$sel:thingName:UpdateConnectivityInfo' :: UpdateConnectivityInfo -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/greengrass/things/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
thingName,
        ByteString
"/connectivityInfo"
      ]

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

-- | /See:/ 'newUpdateConnectivityInfoResponse' smart constructor.
data UpdateConnectivityInfoResponse = UpdateConnectivityInfoResponse'
  { -- | A message about the connectivity information update request.
    UpdateConnectivityInfoResponse -> Maybe Text
message :: Prelude.Maybe Prelude.Text,
    -- | The new version of the connectivity information for the core device.
    UpdateConnectivityInfoResponse -> Maybe Text
version :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateConnectivityInfoResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateConnectivityInfoResponse
-> UpdateConnectivityInfoResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConnectivityInfoResponse
-> UpdateConnectivityInfoResponse -> Bool
$c/= :: UpdateConnectivityInfoResponse
-> UpdateConnectivityInfoResponse -> Bool
== :: UpdateConnectivityInfoResponse
-> UpdateConnectivityInfoResponse -> Bool
$c== :: UpdateConnectivityInfoResponse
-> UpdateConnectivityInfoResponse -> Bool
Prelude.Eq, ReadPrec [UpdateConnectivityInfoResponse]
ReadPrec UpdateConnectivityInfoResponse
Int -> ReadS UpdateConnectivityInfoResponse
ReadS [UpdateConnectivityInfoResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConnectivityInfoResponse]
$creadListPrec :: ReadPrec [UpdateConnectivityInfoResponse]
readPrec :: ReadPrec UpdateConnectivityInfoResponse
$creadPrec :: ReadPrec UpdateConnectivityInfoResponse
readList :: ReadS [UpdateConnectivityInfoResponse]
$creadList :: ReadS [UpdateConnectivityInfoResponse]
readsPrec :: Int -> ReadS UpdateConnectivityInfoResponse
$creadsPrec :: Int -> ReadS UpdateConnectivityInfoResponse
Prelude.Read, Int -> UpdateConnectivityInfoResponse -> ShowS
[UpdateConnectivityInfoResponse] -> ShowS
UpdateConnectivityInfoResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConnectivityInfoResponse] -> ShowS
$cshowList :: [UpdateConnectivityInfoResponse] -> ShowS
show :: UpdateConnectivityInfoResponse -> String
$cshow :: UpdateConnectivityInfoResponse -> String
showsPrec :: Int -> UpdateConnectivityInfoResponse -> ShowS
$cshowsPrec :: Int -> UpdateConnectivityInfoResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateConnectivityInfoResponse x
-> UpdateConnectivityInfoResponse
forall x.
UpdateConnectivityInfoResponse
-> Rep UpdateConnectivityInfoResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateConnectivityInfoResponse x
-> UpdateConnectivityInfoResponse
$cfrom :: forall x.
UpdateConnectivityInfoResponse
-> Rep UpdateConnectivityInfoResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConnectivityInfoResponse' 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:
--
-- 'message', 'updateConnectivityInfoResponse_message' - A message about the connectivity information update request.
--
-- 'version', 'updateConnectivityInfoResponse_version' - The new version of the connectivity information for the core device.
--
-- 'httpStatus', 'updateConnectivityInfoResponse_httpStatus' - The response's http status code.
newUpdateConnectivityInfoResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateConnectivityInfoResponse
newUpdateConnectivityInfoResponse :: Int -> UpdateConnectivityInfoResponse
newUpdateConnectivityInfoResponse Int
pHttpStatus_ =
  UpdateConnectivityInfoResponse'
    { $sel:message:UpdateConnectivityInfoResponse' :: Maybe Text
message =
        forall a. Maybe a
Prelude.Nothing,
      $sel:version:UpdateConnectivityInfoResponse' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateConnectivityInfoResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A message about the connectivity information update request.
updateConnectivityInfoResponse_message :: Lens.Lens' UpdateConnectivityInfoResponse (Prelude.Maybe Prelude.Text)
updateConnectivityInfoResponse_message :: Lens' UpdateConnectivityInfoResponse (Maybe Text)
updateConnectivityInfoResponse_message = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnectivityInfoResponse' {Maybe Text
message :: Maybe Text
$sel:message:UpdateConnectivityInfoResponse' :: UpdateConnectivityInfoResponse -> Maybe Text
message} -> Maybe Text
message) (\s :: UpdateConnectivityInfoResponse
s@UpdateConnectivityInfoResponse' {} Maybe Text
a -> UpdateConnectivityInfoResponse
s {$sel:message:UpdateConnectivityInfoResponse' :: Maybe Text
message = Maybe Text
a} :: UpdateConnectivityInfoResponse)

-- | The new version of the connectivity information for the core device.
updateConnectivityInfoResponse_version :: Lens.Lens' UpdateConnectivityInfoResponse (Prelude.Maybe Prelude.Text)
updateConnectivityInfoResponse_version :: Lens' UpdateConnectivityInfoResponse (Maybe Text)
updateConnectivityInfoResponse_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConnectivityInfoResponse' {Maybe Text
version :: Maybe Text
$sel:version:UpdateConnectivityInfoResponse' :: UpdateConnectivityInfoResponse -> Maybe Text
version} -> Maybe Text
version) (\s :: UpdateConnectivityInfoResponse
s@UpdateConnectivityInfoResponse' {} Maybe Text
a -> UpdateConnectivityInfoResponse
s {$sel:version:UpdateConnectivityInfoResponse' :: Maybe Text
version = Maybe Text
a} :: UpdateConnectivityInfoResponse)

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

instance
  Prelude.NFData
    UpdateConnectivityInfoResponse
  where
  rnf :: UpdateConnectivityInfoResponse -> ()
rnf UpdateConnectivityInfoResponse' {Int
Maybe Text
httpStatus :: Int
version :: Maybe Text
message :: Maybe Text
$sel:httpStatus:UpdateConnectivityInfoResponse' :: UpdateConnectivityInfoResponse -> Int
$sel:version:UpdateConnectivityInfoResponse' :: UpdateConnectivityInfoResponse -> Maybe Text
$sel:message:UpdateConnectivityInfoResponse' :: UpdateConnectivityInfoResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
message
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus