{-# 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.GetFuotaTask
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about a FUOTA task.
module Amazonka.IoTWireless.GetFuotaTask
  ( -- * Creating a Request
    GetFuotaTask (..),
    newGetFuotaTask,

    -- * Request Lenses
    getFuotaTask_id,

    -- * Destructuring the Response
    GetFuotaTaskResponse (..),
    newGetFuotaTaskResponse,

    -- * Response Lenses
    getFuotaTaskResponse_arn,
    getFuotaTaskResponse_createdAt,
    getFuotaTaskResponse_description,
    getFuotaTaskResponse_firmwareUpdateImage,
    getFuotaTaskResponse_firmwareUpdateRole,
    getFuotaTaskResponse_id,
    getFuotaTaskResponse_loRaWAN,
    getFuotaTaskResponse_name,
    getFuotaTaskResponse_status,
    getFuotaTaskResponse_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:/ 'newGetFuotaTask' smart constructor.
data GetFuotaTask = GetFuotaTask'
  { GetFuotaTask -> Text
id :: Prelude.Text
  }
  deriving (GetFuotaTask -> GetFuotaTask -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFuotaTask -> GetFuotaTask -> Bool
$c/= :: GetFuotaTask -> GetFuotaTask -> Bool
== :: GetFuotaTask -> GetFuotaTask -> Bool
$c== :: GetFuotaTask -> GetFuotaTask -> Bool
Prelude.Eq, ReadPrec [GetFuotaTask]
ReadPrec GetFuotaTask
Int -> ReadS GetFuotaTask
ReadS [GetFuotaTask]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFuotaTask]
$creadListPrec :: ReadPrec [GetFuotaTask]
readPrec :: ReadPrec GetFuotaTask
$creadPrec :: ReadPrec GetFuotaTask
readList :: ReadS [GetFuotaTask]
$creadList :: ReadS [GetFuotaTask]
readsPrec :: Int -> ReadS GetFuotaTask
$creadsPrec :: Int -> ReadS GetFuotaTask
Prelude.Read, Int -> GetFuotaTask -> ShowS
[GetFuotaTask] -> ShowS
GetFuotaTask -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFuotaTask] -> ShowS
$cshowList :: [GetFuotaTask] -> ShowS
show :: GetFuotaTask -> String
$cshow :: GetFuotaTask -> String
showsPrec :: Int -> GetFuotaTask -> ShowS
$cshowsPrec :: Int -> GetFuotaTask -> ShowS
Prelude.Show, forall x. Rep GetFuotaTask x -> GetFuotaTask
forall x. GetFuotaTask -> Rep GetFuotaTask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFuotaTask x -> GetFuotaTask
$cfrom :: forall x. GetFuotaTask -> Rep GetFuotaTask x
Prelude.Generic)

-- |
-- Create a value of 'GetFuotaTask' 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:
--
-- 'id', 'getFuotaTask_id' - Undocumented member.
newGetFuotaTask ::
  -- | 'id'
  Prelude.Text ->
  GetFuotaTask
newGetFuotaTask :: Text -> GetFuotaTask
newGetFuotaTask Text
pId_ = GetFuotaTask' {$sel:id:GetFuotaTask' :: Text
id = Text
pId_}

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

instance Core.AWSRequest GetFuotaTask where
  type AWSResponse GetFuotaTask = GetFuotaTaskResponse
  request :: (Service -> Service) -> GetFuotaTask -> Request GetFuotaTask
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetFuotaTask
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetFuotaTask)))
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 POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe LoRaWANFuotaTaskGetInfo
-> Maybe Text
-> Maybe FuotaTaskStatus
-> Int
-> GetFuotaTaskResponse
GetFuotaTaskResponse'
            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
"Arn")
            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
"CreatedAt")
            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
"Description")
            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
"FirmwareUpdateImage")
            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
"FirmwareUpdateRole")
            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
"Id")
            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
"LoRaWAN")
            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
"Name")
            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
"Status")
            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 GetFuotaTask where
  hashWithSalt :: Int -> GetFuotaTask -> Int
hashWithSalt Int
_salt GetFuotaTask' {Text
id :: Text
$sel:id:GetFuotaTask' :: GetFuotaTask -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData GetFuotaTask where
  rnf :: GetFuotaTask -> ()
rnf GetFuotaTask' {Text
id :: Text
$sel:id:GetFuotaTask' :: GetFuotaTask -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
id

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

instance Data.ToPath GetFuotaTask where
  toPath :: GetFuotaTask -> ByteString
toPath GetFuotaTask' {Text
id :: Text
$sel:id:GetFuotaTask' :: GetFuotaTask -> 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 GetFuotaTask where
  toQuery :: GetFuotaTask -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newGetFuotaTaskResponse' smart constructor.
data GetFuotaTaskResponse = GetFuotaTaskResponse'
  { GetFuotaTaskResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    GetFuotaTaskResponse -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    GetFuotaTaskResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    GetFuotaTaskResponse -> Maybe Text
firmwareUpdateImage :: Prelude.Maybe Prelude.Text,
    GetFuotaTaskResponse -> Maybe Text
firmwareUpdateRole :: Prelude.Maybe Prelude.Text,
    GetFuotaTaskResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    GetFuotaTaskResponse -> Maybe LoRaWANFuotaTaskGetInfo
loRaWAN :: Prelude.Maybe LoRaWANFuotaTaskGetInfo,
    GetFuotaTaskResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    GetFuotaTaskResponse -> Maybe FuotaTaskStatus
status :: Prelude.Maybe FuotaTaskStatus,
    -- | The response's http status code.
    GetFuotaTaskResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetFuotaTaskResponse -> GetFuotaTaskResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFuotaTaskResponse -> GetFuotaTaskResponse -> Bool
$c/= :: GetFuotaTaskResponse -> GetFuotaTaskResponse -> Bool
== :: GetFuotaTaskResponse -> GetFuotaTaskResponse -> Bool
$c== :: GetFuotaTaskResponse -> GetFuotaTaskResponse -> Bool
Prelude.Eq, ReadPrec [GetFuotaTaskResponse]
ReadPrec GetFuotaTaskResponse
Int -> ReadS GetFuotaTaskResponse
ReadS [GetFuotaTaskResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFuotaTaskResponse]
$creadListPrec :: ReadPrec [GetFuotaTaskResponse]
readPrec :: ReadPrec GetFuotaTaskResponse
$creadPrec :: ReadPrec GetFuotaTaskResponse
readList :: ReadS [GetFuotaTaskResponse]
$creadList :: ReadS [GetFuotaTaskResponse]
readsPrec :: Int -> ReadS GetFuotaTaskResponse
$creadsPrec :: Int -> ReadS GetFuotaTaskResponse
Prelude.Read, Int -> GetFuotaTaskResponse -> ShowS
[GetFuotaTaskResponse] -> ShowS
GetFuotaTaskResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFuotaTaskResponse] -> ShowS
$cshowList :: [GetFuotaTaskResponse] -> ShowS
show :: GetFuotaTaskResponse -> String
$cshow :: GetFuotaTaskResponse -> String
showsPrec :: Int -> GetFuotaTaskResponse -> ShowS
$cshowsPrec :: Int -> GetFuotaTaskResponse -> ShowS
Prelude.Show, forall x. Rep GetFuotaTaskResponse x -> GetFuotaTaskResponse
forall x. GetFuotaTaskResponse -> Rep GetFuotaTaskResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFuotaTaskResponse x -> GetFuotaTaskResponse
$cfrom :: forall x. GetFuotaTaskResponse -> Rep GetFuotaTaskResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetFuotaTaskResponse' 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:
--
-- 'arn', 'getFuotaTaskResponse_arn' - Undocumented member.
--
-- 'createdAt', 'getFuotaTaskResponse_createdAt' - Undocumented member.
--
-- 'description', 'getFuotaTaskResponse_description' - Undocumented member.
--
-- 'firmwareUpdateImage', 'getFuotaTaskResponse_firmwareUpdateImage' - Undocumented member.
--
-- 'firmwareUpdateRole', 'getFuotaTaskResponse_firmwareUpdateRole' - Undocumented member.
--
-- 'id', 'getFuotaTaskResponse_id' - Undocumented member.
--
-- 'loRaWAN', 'getFuotaTaskResponse_loRaWAN' - Undocumented member.
--
-- 'name', 'getFuotaTaskResponse_name' - Undocumented member.
--
-- 'status', 'getFuotaTaskResponse_status' - Undocumented member.
--
-- 'httpStatus', 'getFuotaTaskResponse_httpStatus' - The response's http status code.
newGetFuotaTaskResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetFuotaTaskResponse
newGetFuotaTaskResponse :: Int -> GetFuotaTaskResponse
newGetFuotaTaskResponse Int
pHttpStatus_ =
  GetFuotaTaskResponse'
    { $sel:arn:GetFuotaTaskResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:GetFuotaTaskResponse' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:description:GetFuotaTaskResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:firmwareUpdateImage:GetFuotaTaskResponse' :: Maybe Text
firmwareUpdateImage = forall a. Maybe a
Prelude.Nothing,
      $sel:firmwareUpdateRole:GetFuotaTaskResponse' :: Maybe Text
firmwareUpdateRole = forall a. Maybe a
Prelude.Nothing,
      $sel:id:GetFuotaTaskResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:loRaWAN:GetFuotaTaskResponse' :: Maybe LoRaWANFuotaTaskGetInfo
loRaWAN = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetFuotaTaskResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:status:GetFuotaTaskResponse' :: Maybe FuotaTaskStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetFuotaTaskResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | Undocumented member.
getFuotaTaskResponse_createdAt :: Lens.Lens' GetFuotaTaskResponse (Prelude.Maybe Prelude.UTCTime)
getFuotaTaskResponse_createdAt :: Lens' GetFuotaTaskResponse (Maybe UTCTime)
getFuotaTaskResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFuotaTaskResponse' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: GetFuotaTaskResponse
s@GetFuotaTaskResponse' {} Maybe POSIX
a -> GetFuotaTaskResponse
s {$sel:createdAt:GetFuotaTaskResponse' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: GetFuotaTaskResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

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

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

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

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

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

-- | Undocumented member.
getFuotaTaskResponse_status :: Lens.Lens' GetFuotaTaskResponse (Prelude.Maybe FuotaTaskStatus)
getFuotaTaskResponse_status :: Lens' GetFuotaTaskResponse (Maybe FuotaTaskStatus)
getFuotaTaskResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFuotaTaskResponse' {Maybe FuotaTaskStatus
status :: Maybe FuotaTaskStatus
$sel:status:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Maybe FuotaTaskStatus
status} -> Maybe FuotaTaskStatus
status) (\s :: GetFuotaTaskResponse
s@GetFuotaTaskResponse' {} Maybe FuotaTaskStatus
a -> GetFuotaTaskResponse
s {$sel:status:GetFuotaTaskResponse' :: Maybe FuotaTaskStatus
status = Maybe FuotaTaskStatus
a} :: GetFuotaTaskResponse)

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

instance Prelude.NFData GetFuotaTaskResponse where
  rnf :: GetFuotaTaskResponse -> ()
rnf GetFuotaTaskResponse' {Int
Maybe Text
Maybe POSIX
Maybe FuotaTaskStatus
Maybe LoRaWANFuotaTaskGetInfo
httpStatus :: Int
status :: Maybe FuotaTaskStatus
name :: Maybe Text
loRaWAN :: Maybe LoRaWANFuotaTaskGetInfo
id :: Maybe Text
firmwareUpdateRole :: Maybe Text
firmwareUpdateImage :: Maybe Text
description :: Maybe Text
createdAt :: Maybe POSIX
arn :: Maybe Text
$sel:httpStatus:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Int
$sel:status:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Maybe FuotaTaskStatus
$sel:name:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Maybe Text
$sel:loRaWAN:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Maybe LoRaWANFuotaTaskGetInfo
$sel:id:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Maybe Text
$sel:firmwareUpdateRole:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Maybe Text
$sel:firmwareUpdateImage:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Maybe Text
$sel:description:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Maybe Text
$sel:createdAt:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Maybe POSIX
$sel:arn:GetFuotaTaskResponse' :: GetFuotaTaskResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      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
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 Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LoRaWANFuotaTaskGetInfo
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 Maybe FuotaTaskStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus