{-# 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.GetWirelessGatewayTask
-- 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 wireless gateway task.
module Amazonka.IoTWireless.GetWirelessGatewayTask
  ( -- * Creating a Request
    GetWirelessGatewayTask (..),
    newGetWirelessGatewayTask,

    -- * Request Lenses
    getWirelessGatewayTask_id,

    -- * Destructuring the Response
    GetWirelessGatewayTaskResponse (..),
    newGetWirelessGatewayTaskResponse,

    -- * Response Lenses
    getWirelessGatewayTaskResponse_lastUplinkReceivedAt,
    getWirelessGatewayTaskResponse_status,
    getWirelessGatewayTaskResponse_taskCreatedAt,
    getWirelessGatewayTaskResponse_wirelessGatewayId,
    getWirelessGatewayTaskResponse_wirelessGatewayTaskDefinitionId,
    getWirelessGatewayTaskResponse_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:/ 'newGetWirelessGatewayTask' smart constructor.
data GetWirelessGatewayTask = GetWirelessGatewayTask'
  { -- | The ID of the resource to get.
    GetWirelessGatewayTask -> Text
id :: Prelude.Text
  }
  deriving (GetWirelessGatewayTask -> GetWirelessGatewayTask -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetWirelessGatewayTask -> GetWirelessGatewayTask -> Bool
$c/= :: GetWirelessGatewayTask -> GetWirelessGatewayTask -> Bool
== :: GetWirelessGatewayTask -> GetWirelessGatewayTask -> Bool
$c== :: GetWirelessGatewayTask -> GetWirelessGatewayTask -> Bool
Prelude.Eq, ReadPrec [GetWirelessGatewayTask]
ReadPrec GetWirelessGatewayTask
Int -> ReadS GetWirelessGatewayTask
ReadS [GetWirelessGatewayTask]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetWirelessGatewayTask]
$creadListPrec :: ReadPrec [GetWirelessGatewayTask]
readPrec :: ReadPrec GetWirelessGatewayTask
$creadPrec :: ReadPrec GetWirelessGatewayTask
readList :: ReadS [GetWirelessGatewayTask]
$creadList :: ReadS [GetWirelessGatewayTask]
readsPrec :: Int -> ReadS GetWirelessGatewayTask
$creadsPrec :: Int -> ReadS GetWirelessGatewayTask
Prelude.Read, Int -> GetWirelessGatewayTask -> ShowS
[GetWirelessGatewayTask] -> ShowS
GetWirelessGatewayTask -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetWirelessGatewayTask] -> ShowS
$cshowList :: [GetWirelessGatewayTask] -> ShowS
show :: GetWirelessGatewayTask -> String
$cshow :: GetWirelessGatewayTask -> String
showsPrec :: Int -> GetWirelessGatewayTask -> ShowS
$cshowsPrec :: Int -> GetWirelessGatewayTask -> ShowS
Prelude.Show, forall x. Rep GetWirelessGatewayTask x -> GetWirelessGatewayTask
forall x. GetWirelessGatewayTask -> Rep GetWirelessGatewayTask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetWirelessGatewayTask x -> GetWirelessGatewayTask
$cfrom :: forall x. GetWirelessGatewayTask -> Rep GetWirelessGatewayTask x
Prelude.Generic)

-- |
-- Create a value of 'GetWirelessGatewayTask' 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', 'getWirelessGatewayTask_id' - The ID of the resource to get.
newGetWirelessGatewayTask ::
  -- | 'id'
  Prelude.Text ->
  GetWirelessGatewayTask
newGetWirelessGatewayTask :: Text -> GetWirelessGatewayTask
newGetWirelessGatewayTask Text
pId_ =
  GetWirelessGatewayTask' {$sel:id:GetWirelessGatewayTask' :: Text
id = Text
pId_}

-- | The ID of the resource to get.
getWirelessGatewayTask_id :: Lens.Lens' GetWirelessGatewayTask Prelude.Text
getWirelessGatewayTask_id :: Lens' GetWirelessGatewayTask Text
getWirelessGatewayTask_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetWirelessGatewayTask' {Text
id :: Text
$sel:id:GetWirelessGatewayTask' :: GetWirelessGatewayTask -> Text
id} -> Text
id) (\s :: GetWirelessGatewayTask
s@GetWirelessGatewayTask' {} Text
a -> GetWirelessGatewayTask
s {$sel:id:GetWirelessGatewayTask' :: Text
id = Text
a} :: GetWirelessGatewayTask)

instance Core.AWSRequest GetWirelessGatewayTask where
  type
    AWSResponse GetWirelessGatewayTask =
      GetWirelessGatewayTaskResponse
  request :: (Service -> Service)
-> GetWirelessGatewayTask -> Request GetWirelessGatewayTask
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 GetWirelessGatewayTask
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetWirelessGatewayTask)))
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 WirelessGatewayTaskStatus
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> GetWirelessGatewayTaskResponse
GetWirelessGatewayTaskResponse'
            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
"LastUplinkReceivedAt")
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"TaskCreatedAt")
            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
"WirelessGatewayId")
            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
"WirelessGatewayTaskDefinitionId")
            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 GetWirelessGatewayTask where
  hashWithSalt :: Int -> GetWirelessGatewayTask -> Int
hashWithSalt Int
_salt GetWirelessGatewayTask' {Text
id :: Text
$sel:id:GetWirelessGatewayTask' :: GetWirelessGatewayTask -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

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

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

instance Data.ToPath GetWirelessGatewayTask where
  toPath :: GetWirelessGatewayTask -> ByteString
toPath GetWirelessGatewayTask' {Text
id :: Text
$sel:id:GetWirelessGatewayTask' :: GetWirelessGatewayTask -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/wireless-gateways/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id, ByteString
"/tasks"]

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

-- | /See:/ 'newGetWirelessGatewayTaskResponse' smart constructor.
data GetWirelessGatewayTaskResponse = GetWirelessGatewayTaskResponse'
  { -- | The date and time when the most recent uplink was received.
    GetWirelessGatewayTaskResponse -> Maybe Text
lastUplinkReceivedAt :: Prelude.Maybe Prelude.Text,
    -- | The status of the request.
    GetWirelessGatewayTaskResponse -> Maybe WirelessGatewayTaskStatus
status :: Prelude.Maybe WirelessGatewayTaskStatus,
    -- | The date and time when the task was created.
    GetWirelessGatewayTaskResponse -> Maybe Text
taskCreatedAt :: Prelude.Maybe Prelude.Text,
    -- | The ID of the wireless gateway.
    GetWirelessGatewayTaskResponse -> Maybe Text
wirelessGatewayId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the WirelessGatewayTask.
    GetWirelessGatewayTaskResponse -> Maybe Text
wirelessGatewayTaskDefinitionId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetWirelessGatewayTaskResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetWirelessGatewayTaskResponse
-> GetWirelessGatewayTaskResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetWirelessGatewayTaskResponse
-> GetWirelessGatewayTaskResponse -> Bool
$c/= :: GetWirelessGatewayTaskResponse
-> GetWirelessGatewayTaskResponse -> Bool
== :: GetWirelessGatewayTaskResponse
-> GetWirelessGatewayTaskResponse -> Bool
$c== :: GetWirelessGatewayTaskResponse
-> GetWirelessGatewayTaskResponse -> Bool
Prelude.Eq, ReadPrec [GetWirelessGatewayTaskResponse]
ReadPrec GetWirelessGatewayTaskResponse
Int -> ReadS GetWirelessGatewayTaskResponse
ReadS [GetWirelessGatewayTaskResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetWirelessGatewayTaskResponse]
$creadListPrec :: ReadPrec [GetWirelessGatewayTaskResponse]
readPrec :: ReadPrec GetWirelessGatewayTaskResponse
$creadPrec :: ReadPrec GetWirelessGatewayTaskResponse
readList :: ReadS [GetWirelessGatewayTaskResponse]
$creadList :: ReadS [GetWirelessGatewayTaskResponse]
readsPrec :: Int -> ReadS GetWirelessGatewayTaskResponse
$creadsPrec :: Int -> ReadS GetWirelessGatewayTaskResponse
Prelude.Read, Int -> GetWirelessGatewayTaskResponse -> ShowS
[GetWirelessGatewayTaskResponse] -> ShowS
GetWirelessGatewayTaskResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetWirelessGatewayTaskResponse] -> ShowS
$cshowList :: [GetWirelessGatewayTaskResponse] -> ShowS
show :: GetWirelessGatewayTaskResponse -> String
$cshow :: GetWirelessGatewayTaskResponse -> String
showsPrec :: Int -> GetWirelessGatewayTaskResponse -> ShowS
$cshowsPrec :: Int -> GetWirelessGatewayTaskResponse -> ShowS
Prelude.Show, forall x.
Rep GetWirelessGatewayTaskResponse x
-> GetWirelessGatewayTaskResponse
forall x.
GetWirelessGatewayTaskResponse
-> Rep GetWirelessGatewayTaskResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetWirelessGatewayTaskResponse x
-> GetWirelessGatewayTaskResponse
$cfrom :: forall x.
GetWirelessGatewayTaskResponse
-> Rep GetWirelessGatewayTaskResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetWirelessGatewayTaskResponse' 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:
--
-- 'lastUplinkReceivedAt', 'getWirelessGatewayTaskResponse_lastUplinkReceivedAt' - The date and time when the most recent uplink was received.
--
-- 'status', 'getWirelessGatewayTaskResponse_status' - The status of the request.
--
-- 'taskCreatedAt', 'getWirelessGatewayTaskResponse_taskCreatedAt' - The date and time when the task was created.
--
-- 'wirelessGatewayId', 'getWirelessGatewayTaskResponse_wirelessGatewayId' - The ID of the wireless gateway.
--
-- 'wirelessGatewayTaskDefinitionId', 'getWirelessGatewayTaskResponse_wirelessGatewayTaskDefinitionId' - The ID of the WirelessGatewayTask.
--
-- 'httpStatus', 'getWirelessGatewayTaskResponse_httpStatus' - The response's http status code.
newGetWirelessGatewayTaskResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetWirelessGatewayTaskResponse
newGetWirelessGatewayTaskResponse :: Int -> GetWirelessGatewayTaskResponse
newGetWirelessGatewayTaskResponse Int
pHttpStatus_ =
  GetWirelessGatewayTaskResponse'
    { $sel:lastUplinkReceivedAt:GetWirelessGatewayTaskResponse' :: Maybe Text
lastUplinkReceivedAt =
        forall a. Maybe a
Prelude.Nothing,
      $sel:status:GetWirelessGatewayTaskResponse' :: Maybe WirelessGatewayTaskStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:taskCreatedAt:GetWirelessGatewayTaskResponse' :: Maybe Text
taskCreatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:wirelessGatewayId:GetWirelessGatewayTaskResponse' :: Maybe Text
wirelessGatewayId = forall a. Maybe a
Prelude.Nothing,
      $sel:wirelessGatewayTaskDefinitionId:GetWirelessGatewayTaskResponse' :: Maybe Text
wirelessGatewayTaskDefinitionId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetWirelessGatewayTaskResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The date and time when the most recent uplink was received.
getWirelessGatewayTaskResponse_lastUplinkReceivedAt :: Lens.Lens' GetWirelessGatewayTaskResponse (Prelude.Maybe Prelude.Text)
getWirelessGatewayTaskResponse_lastUplinkReceivedAt :: Lens' GetWirelessGatewayTaskResponse (Maybe Text)
getWirelessGatewayTaskResponse_lastUplinkReceivedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetWirelessGatewayTaskResponse' {Maybe Text
lastUplinkReceivedAt :: Maybe Text
$sel:lastUplinkReceivedAt:GetWirelessGatewayTaskResponse' :: GetWirelessGatewayTaskResponse -> Maybe Text
lastUplinkReceivedAt} -> Maybe Text
lastUplinkReceivedAt) (\s :: GetWirelessGatewayTaskResponse
s@GetWirelessGatewayTaskResponse' {} Maybe Text
a -> GetWirelessGatewayTaskResponse
s {$sel:lastUplinkReceivedAt:GetWirelessGatewayTaskResponse' :: Maybe Text
lastUplinkReceivedAt = Maybe Text
a} :: GetWirelessGatewayTaskResponse)

-- | The status of the request.
getWirelessGatewayTaskResponse_status :: Lens.Lens' GetWirelessGatewayTaskResponse (Prelude.Maybe WirelessGatewayTaskStatus)
getWirelessGatewayTaskResponse_status :: Lens'
  GetWirelessGatewayTaskResponse (Maybe WirelessGatewayTaskStatus)
getWirelessGatewayTaskResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetWirelessGatewayTaskResponse' {Maybe WirelessGatewayTaskStatus
status :: Maybe WirelessGatewayTaskStatus
$sel:status:GetWirelessGatewayTaskResponse' :: GetWirelessGatewayTaskResponse -> Maybe WirelessGatewayTaskStatus
status} -> Maybe WirelessGatewayTaskStatus
status) (\s :: GetWirelessGatewayTaskResponse
s@GetWirelessGatewayTaskResponse' {} Maybe WirelessGatewayTaskStatus
a -> GetWirelessGatewayTaskResponse
s {$sel:status:GetWirelessGatewayTaskResponse' :: Maybe WirelessGatewayTaskStatus
status = Maybe WirelessGatewayTaskStatus
a} :: GetWirelessGatewayTaskResponse)

-- | The date and time when the task was created.
getWirelessGatewayTaskResponse_taskCreatedAt :: Lens.Lens' GetWirelessGatewayTaskResponse (Prelude.Maybe Prelude.Text)
getWirelessGatewayTaskResponse_taskCreatedAt :: Lens' GetWirelessGatewayTaskResponse (Maybe Text)
getWirelessGatewayTaskResponse_taskCreatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetWirelessGatewayTaskResponse' {Maybe Text
taskCreatedAt :: Maybe Text
$sel:taskCreatedAt:GetWirelessGatewayTaskResponse' :: GetWirelessGatewayTaskResponse -> Maybe Text
taskCreatedAt} -> Maybe Text
taskCreatedAt) (\s :: GetWirelessGatewayTaskResponse
s@GetWirelessGatewayTaskResponse' {} Maybe Text
a -> GetWirelessGatewayTaskResponse
s {$sel:taskCreatedAt:GetWirelessGatewayTaskResponse' :: Maybe Text
taskCreatedAt = Maybe Text
a} :: GetWirelessGatewayTaskResponse)

-- | The ID of the wireless gateway.
getWirelessGatewayTaskResponse_wirelessGatewayId :: Lens.Lens' GetWirelessGatewayTaskResponse (Prelude.Maybe Prelude.Text)
getWirelessGatewayTaskResponse_wirelessGatewayId :: Lens' GetWirelessGatewayTaskResponse (Maybe Text)
getWirelessGatewayTaskResponse_wirelessGatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetWirelessGatewayTaskResponse' {Maybe Text
wirelessGatewayId :: Maybe Text
$sel:wirelessGatewayId:GetWirelessGatewayTaskResponse' :: GetWirelessGatewayTaskResponse -> Maybe Text
wirelessGatewayId} -> Maybe Text
wirelessGatewayId) (\s :: GetWirelessGatewayTaskResponse
s@GetWirelessGatewayTaskResponse' {} Maybe Text
a -> GetWirelessGatewayTaskResponse
s {$sel:wirelessGatewayId:GetWirelessGatewayTaskResponse' :: Maybe Text
wirelessGatewayId = Maybe Text
a} :: GetWirelessGatewayTaskResponse)

-- | The ID of the WirelessGatewayTask.
getWirelessGatewayTaskResponse_wirelessGatewayTaskDefinitionId :: Lens.Lens' GetWirelessGatewayTaskResponse (Prelude.Maybe Prelude.Text)
getWirelessGatewayTaskResponse_wirelessGatewayTaskDefinitionId :: Lens' GetWirelessGatewayTaskResponse (Maybe Text)
getWirelessGatewayTaskResponse_wirelessGatewayTaskDefinitionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetWirelessGatewayTaskResponse' {Maybe Text
wirelessGatewayTaskDefinitionId :: Maybe Text
$sel:wirelessGatewayTaskDefinitionId:GetWirelessGatewayTaskResponse' :: GetWirelessGatewayTaskResponse -> Maybe Text
wirelessGatewayTaskDefinitionId} -> Maybe Text
wirelessGatewayTaskDefinitionId) (\s :: GetWirelessGatewayTaskResponse
s@GetWirelessGatewayTaskResponse' {} Maybe Text
a -> GetWirelessGatewayTaskResponse
s {$sel:wirelessGatewayTaskDefinitionId:GetWirelessGatewayTaskResponse' :: Maybe Text
wirelessGatewayTaskDefinitionId = Maybe Text
a} :: GetWirelessGatewayTaskResponse)

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

instance
  Prelude.NFData
    GetWirelessGatewayTaskResponse
  where
  rnf :: GetWirelessGatewayTaskResponse -> ()
rnf GetWirelessGatewayTaskResponse' {Int
Maybe Text
Maybe WirelessGatewayTaskStatus
httpStatus :: Int
wirelessGatewayTaskDefinitionId :: Maybe Text
wirelessGatewayId :: Maybe Text
taskCreatedAt :: Maybe Text
status :: Maybe WirelessGatewayTaskStatus
lastUplinkReceivedAt :: Maybe Text
$sel:httpStatus:GetWirelessGatewayTaskResponse' :: GetWirelessGatewayTaskResponse -> Int
$sel:wirelessGatewayTaskDefinitionId:GetWirelessGatewayTaskResponse' :: GetWirelessGatewayTaskResponse -> Maybe Text
$sel:wirelessGatewayId:GetWirelessGatewayTaskResponse' :: GetWirelessGatewayTaskResponse -> Maybe Text
$sel:taskCreatedAt:GetWirelessGatewayTaskResponse' :: GetWirelessGatewayTaskResponse -> Maybe Text
$sel:status:GetWirelessGatewayTaskResponse' :: GetWirelessGatewayTaskResponse -> Maybe WirelessGatewayTaskStatus
$sel:lastUplinkReceivedAt:GetWirelessGatewayTaskResponse' :: GetWirelessGatewayTaskResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastUplinkReceivedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe WirelessGatewayTaskStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
taskCreatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
wirelessGatewayId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
wirelessGatewayTaskDefinitionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus