{-# 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.UpdateFuotaTask
-- 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 FUOTA task.
module Amazonka.IoTWireless.UpdateFuotaTask
  ( -- * Creating a Request
    UpdateFuotaTask (..),
    newUpdateFuotaTask,

    -- * Request Lenses
    updateFuotaTask_description,
    updateFuotaTask_firmwareUpdateImage,
    updateFuotaTask_firmwareUpdateRole,
    updateFuotaTask_loRaWAN,
    updateFuotaTask_name,
    updateFuotaTask_id,

    -- * Destructuring the Response
    UpdateFuotaTaskResponse (..),
    newUpdateFuotaTaskResponse,

    -- * Response Lenses
    updateFuotaTaskResponse_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:/ 'newUpdateFuotaTask' smart constructor.
data UpdateFuotaTask = UpdateFuotaTask'
  { UpdateFuotaTask -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    UpdateFuotaTask -> Maybe Text
firmwareUpdateImage :: Prelude.Maybe Prelude.Text,
    UpdateFuotaTask -> Maybe Text
firmwareUpdateRole :: Prelude.Maybe Prelude.Text,
    UpdateFuotaTask -> Maybe LoRaWANFuotaTask
loRaWAN :: Prelude.Maybe LoRaWANFuotaTask,
    UpdateFuotaTask -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    UpdateFuotaTask -> Text
id :: Prelude.Text
  }
  deriving (UpdateFuotaTask -> UpdateFuotaTask -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFuotaTask -> UpdateFuotaTask -> Bool
$c/= :: UpdateFuotaTask -> UpdateFuotaTask -> Bool
== :: UpdateFuotaTask -> UpdateFuotaTask -> Bool
$c== :: UpdateFuotaTask -> UpdateFuotaTask -> Bool
Prelude.Eq, ReadPrec [UpdateFuotaTask]
ReadPrec UpdateFuotaTask
Int -> ReadS UpdateFuotaTask
ReadS [UpdateFuotaTask]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFuotaTask]
$creadListPrec :: ReadPrec [UpdateFuotaTask]
readPrec :: ReadPrec UpdateFuotaTask
$creadPrec :: ReadPrec UpdateFuotaTask
readList :: ReadS [UpdateFuotaTask]
$creadList :: ReadS [UpdateFuotaTask]
readsPrec :: Int -> ReadS UpdateFuotaTask
$creadsPrec :: Int -> ReadS UpdateFuotaTask
Prelude.Read, Int -> UpdateFuotaTask -> ShowS
[UpdateFuotaTask] -> ShowS
UpdateFuotaTask -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFuotaTask] -> ShowS
$cshowList :: [UpdateFuotaTask] -> ShowS
show :: UpdateFuotaTask -> String
$cshow :: UpdateFuotaTask -> String
showsPrec :: Int -> UpdateFuotaTask -> ShowS
$cshowsPrec :: Int -> UpdateFuotaTask -> ShowS
Prelude.Show, forall x. Rep UpdateFuotaTask x -> UpdateFuotaTask
forall x. UpdateFuotaTask -> Rep UpdateFuotaTask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateFuotaTask x -> UpdateFuotaTask
$cfrom :: forall x. UpdateFuotaTask -> Rep UpdateFuotaTask x
Prelude.Generic)

-- |
-- Create a value of 'UpdateFuotaTask' 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', 'updateFuotaTask_description' - Undocumented member.
--
-- 'firmwareUpdateImage', 'updateFuotaTask_firmwareUpdateImage' - Undocumented member.
--
-- 'firmwareUpdateRole', 'updateFuotaTask_firmwareUpdateRole' - Undocumented member.
--
-- 'loRaWAN', 'updateFuotaTask_loRaWAN' - Undocumented member.
--
-- 'name', 'updateFuotaTask_name' - Undocumented member.
--
-- 'id', 'updateFuotaTask_id' - Undocumented member.
newUpdateFuotaTask ::
  -- | 'id'
  Prelude.Text ->
  UpdateFuotaTask
newUpdateFuotaTask :: Text -> UpdateFuotaTask
newUpdateFuotaTask Text
pId_ =
  UpdateFuotaTask'
    { $sel:description:UpdateFuotaTask' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:firmwareUpdateImage:UpdateFuotaTask' :: Maybe Text
firmwareUpdateImage = forall a. Maybe a
Prelude.Nothing,
      $sel:firmwareUpdateRole:UpdateFuotaTask' :: Maybe Text
firmwareUpdateRole = forall a. Maybe a
Prelude.Nothing,
      $sel:loRaWAN:UpdateFuotaTask' :: Maybe LoRaWANFuotaTask
loRaWAN = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateFuotaTask' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:id:UpdateFuotaTask' :: Text
id = Text
pId_
    }

-- | Undocumented member.
updateFuotaTask_description :: Lens.Lens' UpdateFuotaTask (Prelude.Maybe Prelude.Text)
updateFuotaTask_description :: Lens' UpdateFuotaTask (Maybe Text)
updateFuotaTask_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFuotaTask' {Maybe Text
description :: Maybe Text
$sel:description:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateFuotaTask
s@UpdateFuotaTask' {} Maybe Text
a -> UpdateFuotaTask
s {$sel:description:UpdateFuotaTask' :: Maybe Text
description = Maybe Text
a} :: UpdateFuotaTask)

-- | Undocumented member.
updateFuotaTask_firmwareUpdateImage :: Lens.Lens' UpdateFuotaTask (Prelude.Maybe Prelude.Text)
updateFuotaTask_firmwareUpdateImage :: Lens' UpdateFuotaTask (Maybe Text)
updateFuotaTask_firmwareUpdateImage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFuotaTask' {Maybe Text
firmwareUpdateImage :: Maybe Text
$sel:firmwareUpdateImage:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
firmwareUpdateImage} -> Maybe Text
firmwareUpdateImage) (\s :: UpdateFuotaTask
s@UpdateFuotaTask' {} Maybe Text
a -> UpdateFuotaTask
s {$sel:firmwareUpdateImage:UpdateFuotaTask' :: Maybe Text
firmwareUpdateImage = Maybe Text
a} :: UpdateFuotaTask)

-- | Undocumented member.
updateFuotaTask_firmwareUpdateRole :: Lens.Lens' UpdateFuotaTask (Prelude.Maybe Prelude.Text)
updateFuotaTask_firmwareUpdateRole :: Lens' UpdateFuotaTask (Maybe Text)
updateFuotaTask_firmwareUpdateRole = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFuotaTask' {Maybe Text
firmwareUpdateRole :: Maybe Text
$sel:firmwareUpdateRole:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
firmwareUpdateRole} -> Maybe Text
firmwareUpdateRole) (\s :: UpdateFuotaTask
s@UpdateFuotaTask' {} Maybe Text
a -> UpdateFuotaTask
s {$sel:firmwareUpdateRole:UpdateFuotaTask' :: Maybe Text
firmwareUpdateRole = Maybe Text
a} :: UpdateFuotaTask)

-- | Undocumented member.
updateFuotaTask_loRaWAN :: Lens.Lens' UpdateFuotaTask (Prelude.Maybe LoRaWANFuotaTask)
updateFuotaTask_loRaWAN :: Lens' UpdateFuotaTask (Maybe LoRaWANFuotaTask)
updateFuotaTask_loRaWAN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFuotaTask' {Maybe LoRaWANFuotaTask
loRaWAN :: Maybe LoRaWANFuotaTask
$sel:loRaWAN:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe LoRaWANFuotaTask
loRaWAN} -> Maybe LoRaWANFuotaTask
loRaWAN) (\s :: UpdateFuotaTask
s@UpdateFuotaTask' {} Maybe LoRaWANFuotaTask
a -> UpdateFuotaTask
s {$sel:loRaWAN:UpdateFuotaTask' :: Maybe LoRaWANFuotaTask
loRaWAN = Maybe LoRaWANFuotaTask
a} :: UpdateFuotaTask)

-- | Undocumented member.
updateFuotaTask_name :: Lens.Lens' UpdateFuotaTask (Prelude.Maybe Prelude.Text)
updateFuotaTask_name :: Lens' UpdateFuotaTask (Maybe Text)
updateFuotaTask_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFuotaTask' {Maybe Text
name :: Maybe Text
$sel:name:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateFuotaTask
s@UpdateFuotaTask' {} Maybe Text
a -> UpdateFuotaTask
s {$sel:name:UpdateFuotaTask' :: Maybe Text
name = Maybe Text
a} :: UpdateFuotaTask)

-- | Undocumented member.
updateFuotaTask_id :: Lens.Lens' UpdateFuotaTask Prelude.Text
updateFuotaTask_id :: Lens' UpdateFuotaTask Text
updateFuotaTask_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFuotaTask' {Text
id :: Text
$sel:id:UpdateFuotaTask' :: UpdateFuotaTask -> Text
id} -> Text
id) (\s :: UpdateFuotaTask
s@UpdateFuotaTask' {} Text
a -> UpdateFuotaTask
s {$sel:id:UpdateFuotaTask' :: Text
id = Text
a} :: UpdateFuotaTask)

instance Core.AWSRequest UpdateFuotaTask where
  type
    AWSResponse UpdateFuotaTask =
      UpdateFuotaTaskResponse
  request :: (Service -> Service) -> UpdateFuotaTask -> Request UpdateFuotaTask
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 UpdateFuotaTask
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateFuotaTask)))
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 -> UpdateFuotaTaskResponse
UpdateFuotaTaskResponse'
            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 UpdateFuotaTask where
  hashWithSalt :: Int -> UpdateFuotaTask -> Int
hashWithSalt Int
_salt UpdateFuotaTask' {Maybe Text
Maybe LoRaWANFuotaTask
Text
id :: Text
name :: Maybe Text
loRaWAN :: Maybe LoRaWANFuotaTask
firmwareUpdateRole :: Maybe Text
firmwareUpdateImage :: Maybe Text
description :: Maybe Text
$sel:id:UpdateFuotaTask' :: UpdateFuotaTask -> Text
$sel:name:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:loRaWAN:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe LoRaWANFuotaTask
$sel:firmwareUpdateRole:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:firmwareUpdateImage:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:description:UpdateFuotaTask' :: UpdateFuotaTask -> 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 Text
firmwareUpdateImage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
firmwareUpdateRole
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LoRaWANFuotaTask
loRaWAN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData UpdateFuotaTask where
  rnf :: UpdateFuotaTask -> ()
rnf UpdateFuotaTask' {Maybe Text
Maybe LoRaWANFuotaTask
Text
id :: Text
name :: Maybe Text
loRaWAN :: Maybe LoRaWANFuotaTask
firmwareUpdateRole :: Maybe Text
firmwareUpdateImage :: Maybe Text
description :: Maybe Text
$sel:id:UpdateFuotaTask' :: UpdateFuotaTask -> Text
$sel:name:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:loRaWAN:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe LoRaWANFuotaTask
$sel:firmwareUpdateRole:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:firmwareUpdateImage:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:description:UpdateFuotaTask' :: UpdateFuotaTask -> 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 Text
firmwareUpdateImage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
firmwareUpdateRole
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LoRaWANFuotaTask
loRaWAN
      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 Text
id

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

instance Data.ToJSON UpdateFuotaTask where
  toJSON :: UpdateFuotaTask -> Value
toJSON UpdateFuotaTask' {Maybe Text
Maybe LoRaWANFuotaTask
Text
id :: Text
name :: Maybe Text
loRaWAN :: Maybe LoRaWANFuotaTask
firmwareUpdateRole :: Maybe Text
firmwareUpdateImage :: Maybe Text
description :: Maybe Text
$sel:id:UpdateFuotaTask' :: UpdateFuotaTask -> Text
$sel:name:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:loRaWAN:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe LoRaWANFuotaTask
$sel:firmwareUpdateRole:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:firmwareUpdateImage:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:description:UpdateFuotaTask' :: UpdateFuotaTask -> 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
"FirmwareUpdateImage" 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
firmwareUpdateImage,
            (Key
"FirmwareUpdateRole" 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
firmwareUpdateRole,
            (Key
"LoRaWAN" 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 LoRaWANFuotaTask
loRaWAN,
            (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
          ]
      )

instance Data.ToPath UpdateFuotaTask where
  toPath :: UpdateFuotaTask -> ByteString
toPath UpdateFuotaTask' {Maybe Text
Maybe LoRaWANFuotaTask
Text
id :: Text
name :: Maybe Text
loRaWAN :: Maybe LoRaWANFuotaTask
firmwareUpdateRole :: Maybe Text
firmwareUpdateImage :: Maybe Text
description :: Maybe Text
$sel:id:UpdateFuotaTask' :: UpdateFuotaTask -> Text
$sel:name:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:loRaWAN:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe LoRaWANFuotaTask
$sel:firmwareUpdateRole:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:firmwareUpdateImage:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
$sel:description:UpdateFuotaTask' :: UpdateFuotaTask -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/fuota-tasks/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

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

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

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

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