{-# 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.IoTWireless.UpdateWirelessGateway
-- 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 properties of a wireless gateway.
module Amazonka.IoTWireless.UpdateWirelessGateway
  ( -- * Creating a Request
    UpdateWirelessGateway (..),
    newUpdateWirelessGateway,

    -- * Request Lenses
    updateWirelessGateway_description,
    updateWirelessGateway_joinEuiFilters,
    updateWirelessGateway_name,
    updateWirelessGateway_netIdFilters,
    updateWirelessGateway_id,

    -- * Destructuring the Response
    UpdateWirelessGatewayResponse (..),
    newUpdateWirelessGatewayResponse,

    -- * Response Lenses
    updateWirelessGatewayResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateWirelessGateway' smart constructor.
data UpdateWirelessGateway = UpdateWirelessGateway'
  { -- | A new description of the resource.
    UpdateWirelessGateway -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    UpdateWirelessGateway -> Maybe [NonEmpty Text]
joinEuiFilters :: Prelude.Maybe [Prelude.NonEmpty Prelude.Text],
    -- | The new name of the resource.
    UpdateWirelessGateway -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    UpdateWirelessGateway -> Maybe [Text]
netIdFilters :: Prelude.Maybe [Prelude.Text],
    -- | The ID of the resource to update.
    UpdateWirelessGateway -> Text
id :: Prelude.Text
  }
  deriving (UpdateWirelessGateway -> UpdateWirelessGateway -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateWirelessGateway -> UpdateWirelessGateway -> Bool
$c/= :: UpdateWirelessGateway -> UpdateWirelessGateway -> Bool
== :: UpdateWirelessGateway -> UpdateWirelessGateway -> Bool
$c== :: UpdateWirelessGateway -> UpdateWirelessGateway -> Bool
Prelude.Eq, ReadPrec [UpdateWirelessGateway]
ReadPrec UpdateWirelessGateway
Int -> ReadS UpdateWirelessGateway
ReadS [UpdateWirelessGateway]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateWirelessGateway]
$creadListPrec :: ReadPrec [UpdateWirelessGateway]
readPrec :: ReadPrec UpdateWirelessGateway
$creadPrec :: ReadPrec UpdateWirelessGateway
readList :: ReadS [UpdateWirelessGateway]
$creadList :: ReadS [UpdateWirelessGateway]
readsPrec :: Int -> ReadS UpdateWirelessGateway
$creadsPrec :: Int -> ReadS UpdateWirelessGateway
Prelude.Read, Int -> UpdateWirelessGateway -> ShowS
[UpdateWirelessGateway] -> ShowS
UpdateWirelessGateway -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateWirelessGateway] -> ShowS
$cshowList :: [UpdateWirelessGateway] -> ShowS
show :: UpdateWirelessGateway -> String
$cshow :: UpdateWirelessGateway -> String
showsPrec :: Int -> UpdateWirelessGateway -> ShowS
$cshowsPrec :: Int -> UpdateWirelessGateway -> ShowS
Prelude.Show, forall x. Rep UpdateWirelessGateway x -> UpdateWirelessGateway
forall x. UpdateWirelessGateway -> Rep UpdateWirelessGateway x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateWirelessGateway x -> UpdateWirelessGateway
$cfrom :: forall x. UpdateWirelessGateway -> Rep UpdateWirelessGateway x
Prelude.Generic)

-- |
-- Create a value of 'UpdateWirelessGateway' 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:
--
-- 'description', 'updateWirelessGateway_description' - A new description of the resource.
--
-- 'joinEuiFilters', 'updateWirelessGateway_joinEuiFilters' - Undocumented member.
--
-- 'name', 'updateWirelessGateway_name' - The new name of the resource.
--
-- 'netIdFilters', 'updateWirelessGateway_netIdFilters' - Undocumented member.
--
-- 'id', 'updateWirelessGateway_id' - The ID of the resource to update.
newUpdateWirelessGateway ::
  -- | 'id'
  Prelude.Text ->
  UpdateWirelessGateway
newUpdateWirelessGateway :: Text -> UpdateWirelessGateway
newUpdateWirelessGateway Text
pId_ =
  UpdateWirelessGateway'
    { $sel:description:UpdateWirelessGateway' :: Maybe Text
description =
        forall a. Maybe a
Prelude.Nothing,
      $sel:joinEuiFilters:UpdateWirelessGateway' :: Maybe [NonEmpty Text]
joinEuiFilters = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateWirelessGateway' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:netIdFilters:UpdateWirelessGateway' :: Maybe [Text]
netIdFilters = forall a. Maybe a
Prelude.Nothing,
      $sel:id:UpdateWirelessGateway' :: Text
id = Text
pId_
    }

-- | A new description of the resource.
updateWirelessGateway_description :: Lens.Lens' UpdateWirelessGateway (Prelude.Maybe Prelude.Text)
updateWirelessGateway_description :: Lens' UpdateWirelessGateway (Maybe Text)
updateWirelessGateway_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWirelessGateway' {Maybe Text
description :: Maybe Text
$sel:description:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateWirelessGateway
s@UpdateWirelessGateway' {} Maybe Text
a -> UpdateWirelessGateway
s {$sel:description:UpdateWirelessGateway' :: Maybe Text
description = Maybe Text
a} :: UpdateWirelessGateway)

-- | Undocumented member.
updateWirelessGateway_joinEuiFilters :: Lens.Lens' UpdateWirelessGateway (Prelude.Maybe [Prelude.NonEmpty Prelude.Text])
updateWirelessGateway_joinEuiFilters :: Lens' UpdateWirelessGateway (Maybe [NonEmpty Text])
updateWirelessGateway_joinEuiFilters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWirelessGateway' {Maybe [NonEmpty Text]
joinEuiFilters :: Maybe [NonEmpty Text]
$sel:joinEuiFilters:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe [NonEmpty Text]
joinEuiFilters} -> Maybe [NonEmpty Text]
joinEuiFilters) (\s :: UpdateWirelessGateway
s@UpdateWirelessGateway' {} Maybe [NonEmpty Text]
a -> UpdateWirelessGateway
s {$sel:joinEuiFilters:UpdateWirelessGateway' :: Maybe [NonEmpty Text]
joinEuiFilters = Maybe [NonEmpty Text]
a} :: UpdateWirelessGateway) 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 new name of the resource.
updateWirelessGateway_name :: Lens.Lens' UpdateWirelessGateway (Prelude.Maybe Prelude.Text)
updateWirelessGateway_name :: Lens' UpdateWirelessGateway (Maybe Text)
updateWirelessGateway_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWirelessGateway' {Maybe Text
name :: Maybe Text
$sel:name:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateWirelessGateway
s@UpdateWirelessGateway' {} Maybe Text
a -> UpdateWirelessGateway
s {$sel:name:UpdateWirelessGateway' :: Maybe Text
name = Maybe Text
a} :: UpdateWirelessGateway)

-- | Undocumented member.
updateWirelessGateway_netIdFilters :: Lens.Lens' UpdateWirelessGateway (Prelude.Maybe [Prelude.Text])
updateWirelessGateway_netIdFilters :: Lens' UpdateWirelessGateway (Maybe [Text])
updateWirelessGateway_netIdFilters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWirelessGateway' {Maybe [Text]
netIdFilters :: Maybe [Text]
$sel:netIdFilters:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe [Text]
netIdFilters} -> Maybe [Text]
netIdFilters) (\s :: UpdateWirelessGateway
s@UpdateWirelessGateway' {} Maybe [Text]
a -> UpdateWirelessGateway
s {$sel:netIdFilters:UpdateWirelessGateway' :: Maybe [Text]
netIdFilters = Maybe [Text]
a} :: UpdateWirelessGateway) 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 ID of the resource to update.
updateWirelessGateway_id :: Lens.Lens' UpdateWirelessGateway Prelude.Text
updateWirelessGateway_id :: Lens' UpdateWirelessGateway Text
updateWirelessGateway_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWirelessGateway' {Text
id :: Text
$sel:id:UpdateWirelessGateway' :: UpdateWirelessGateway -> Text
id} -> Text
id) (\s :: UpdateWirelessGateway
s@UpdateWirelessGateway' {} Text
a -> UpdateWirelessGateway
s {$sel:id:UpdateWirelessGateway' :: Text
id = Text
a} :: UpdateWirelessGateway)

instance Core.AWSRequest UpdateWirelessGateway where
  type
    AWSResponse UpdateWirelessGateway =
      UpdateWirelessGatewayResponse
  request :: (Service -> Service)
-> UpdateWirelessGateway -> Request UpdateWirelessGateway
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 UpdateWirelessGateway
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateWirelessGateway)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> UpdateWirelessGatewayResponse
UpdateWirelessGatewayResponse'
            forall (f :: * -> *) a b. Functor 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 UpdateWirelessGateway where
  hashWithSalt :: Int -> UpdateWirelessGateway -> Int
hashWithSalt Int
_salt UpdateWirelessGateway' {Maybe [NonEmpty Text]
Maybe [Text]
Maybe Text
Text
id :: Text
netIdFilters :: Maybe [Text]
name :: Maybe Text
joinEuiFilters :: Maybe [NonEmpty Text]
description :: Maybe Text
$sel:id:UpdateWirelessGateway' :: UpdateWirelessGateway -> Text
$sel:netIdFilters:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe [Text]
$sel:name:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe Text
$sel:joinEuiFilters:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe [NonEmpty Text]
$sel:description:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [NonEmpty Text]
joinEuiFilters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
netIdFilters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData UpdateWirelessGateway where
  rnf :: UpdateWirelessGateway -> ()
rnf UpdateWirelessGateway' {Maybe [NonEmpty Text]
Maybe [Text]
Maybe Text
Text
id :: Text
netIdFilters :: Maybe [Text]
name :: Maybe Text
joinEuiFilters :: Maybe [NonEmpty Text]
description :: Maybe Text
$sel:id:UpdateWirelessGateway' :: UpdateWirelessGateway -> Text
$sel:netIdFilters:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe [Text]
$sel:name:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe Text
$sel:joinEuiFilters:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe [NonEmpty Text]
$sel:description:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe Text
..} =
    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 [NonEmpty Text]
joinEuiFilters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
netIdFilters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

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

instance Data.ToJSON UpdateWirelessGateway where
  toJSON :: UpdateWirelessGateway -> Value
toJSON UpdateWirelessGateway' {Maybe [NonEmpty Text]
Maybe [Text]
Maybe Text
Text
id :: Text
netIdFilters :: Maybe [Text]
name :: Maybe Text
joinEuiFilters :: Maybe [NonEmpty Text]
description :: Maybe Text
$sel:id:UpdateWirelessGateway' :: UpdateWirelessGateway -> Text
$sel:netIdFilters:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe [Text]
$sel:name:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe Text
$sel:joinEuiFilters:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe [NonEmpty Text]
$sel:description:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
"JoinEuiFilters" 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 [NonEmpty Text]
joinEuiFilters,
            (Key
"Name" 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
name,
            (Key
"NetIdFilters" 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]
netIdFilters
          ]
      )

instance Data.ToPath UpdateWirelessGateway where
  toPath :: UpdateWirelessGateway -> ByteString
toPath UpdateWirelessGateway' {Maybe [NonEmpty Text]
Maybe [Text]
Maybe Text
Text
id :: Text
netIdFilters :: Maybe [Text]
name :: Maybe Text
joinEuiFilters :: Maybe [NonEmpty Text]
description :: Maybe Text
$sel:id:UpdateWirelessGateway' :: UpdateWirelessGateway -> Text
$sel:netIdFilters:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe [Text]
$sel:name:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe Text
$sel:joinEuiFilters:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe [NonEmpty Text]
$sel:description:UpdateWirelessGateway' :: UpdateWirelessGateway -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/wireless-gateways/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

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

-- |
-- Create a value of 'UpdateWirelessGatewayResponse' 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:
--
-- 'httpStatus', 'updateWirelessGatewayResponse_httpStatus' - The response's http status code.
newUpdateWirelessGatewayResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateWirelessGatewayResponse
newUpdateWirelessGatewayResponse :: Int -> UpdateWirelessGatewayResponse
newUpdateWirelessGatewayResponse Int
pHttpStatus_ =
  UpdateWirelessGatewayResponse'
    { $sel:httpStatus:UpdateWirelessGatewayResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData UpdateWirelessGatewayResponse where
  rnf :: UpdateWirelessGatewayResponse -> ()
rnf UpdateWirelessGatewayResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateWirelessGatewayResponse' :: UpdateWirelessGatewayResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus