{-# 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.Panorama.DescribeDeviceJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about a device job.
module Amazonka.Panorama.DescribeDeviceJob
  ( -- * Creating a Request
    DescribeDeviceJob (..),
    newDescribeDeviceJob,

    -- * Request Lenses
    describeDeviceJob_jobId,

    -- * Destructuring the Response
    DescribeDeviceJobResponse (..),
    newDescribeDeviceJobResponse,

    -- * Response Lenses
    describeDeviceJobResponse_createdTime,
    describeDeviceJobResponse_deviceArn,
    describeDeviceJobResponse_deviceId,
    describeDeviceJobResponse_deviceName,
    describeDeviceJobResponse_deviceType,
    describeDeviceJobResponse_imageVersion,
    describeDeviceJobResponse_jobId,
    describeDeviceJobResponse_jobType,
    describeDeviceJobResponse_status,
    describeDeviceJobResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeDeviceJob' smart constructor.
data DescribeDeviceJob = DescribeDeviceJob'
  { -- | The job\'s ID.
    DescribeDeviceJob -> Text
jobId :: Prelude.Text
  }
  deriving (DescribeDeviceJob -> DescribeDeviceJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDeviceJob -> DescribeDeviceJob -> Bool
$c/= :: DescribeDeviceJob -> DescribeDeviceJob -> Bool
== :: DescribeDeviceJob -> DescribeDeviceJob -> Bool
$c== :: DescribeDeviceJob -> DescribeDeviceJob -> Bool
Prelude.Eq, ReadPrec [DescribeDeviceJob]
ReadPrec DescribeDeviceJob
Int -> ReadS DescribeDeviceJob
ReadS [DescribeDeviceJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDeviceJob]
$creadListPrec :: ReadPrec [DescribeDeviceJob]
readPrec :: ReadPrec DescribeDeviceJob
$creadPrec :: ReadPrec DescribeDeviceJob
readList :: ReadS [DescribeDeviceJob]
$creadList :: ReadS [DescribeDeviceJob]
readsPrec :: Int -> ReadS DescribeDeviceJob
$creadsPrec :: Int -> ReadS DescribeDeviceJob
Prelude.Read, Int -> DescribeDeviceJob -> ShowS
[DescribeDeviceJob] -> ShowS
DescribeDeviceJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDeviceJob] -> ShowS
$cshowList :: [DescribeDeviceJob] -> ShowS
show :: DescribeDeviceJob -> String
$cshow :: DescribeDeviceJob -> String
showsPrec :: Int -> DescribeDeviceJob -> ShowS
$cshowsPrec :: Int -> DescribeDeviceJob -> ShowS
Prelude.Show, forall x. Rep DescribeDeviceJob x -> DescribeDeviceJob
forall x. DescribeDeviceJob -> Rep DescribeDeviceJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeDeviceJob x -> DescribeDeviceJob
$cfrom :: forall x. DescribeDeviceJob -> Rep DescribeDeviceJob x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDeviceJob' 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:
--
-- 'jobId', 'describeDeviceJob_jobId' - The job\'s ID.
newDescribeDeviceJob ::
  -- | 'jobId'
  Prelude.Text ->
  DescribeDeviceJob
newDescribeDeviceJob :: Text -> DescribeDeviceJob
newDescribeDeviceJob Text
pJobId_ =
  DescribeDeviceJob' {$sel:jobId:DescribeDeviceJob' :: Text
jobId = Text
pJobId_}

-- | The job\'s ID.
describeDeviceJob_jobId :: Lens.Lens' DescribeDeviceJob Prelude.Text
describeDeviceJob_jobId :: Lens' DescribeDeviceJob Text
describeDeviceJob_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDeviceJob' {Text
jobId :: Text
$sel:jobId:DescribeDeviceJob' :: DescribeDeviceJob -> Text
jobId} -> Text
jobId) (\s :: DescribeDeviceJob
s@DescribeDeviceJob' {} Text
a -> DescribeDeviceJob
s {$sel:jobId:DescribeDeviceJob' :: Text
jobId = Text
a} :: DescribeDeviceJob)

instance Core.AWSRequest DescribeDeviceJob where
  type
    AWSResponse DescribeDeviceJob =
      DescribeDeviceJobResponse
  request :: (Service -> Service)
-> DescribeDeviceJob -> Request DescribeDeviceJob
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 DescribeDeviceJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeDeviceJob)))
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 POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe DeviceType
-> Maybe Text
-> Maybe Text
-> Maybe JobType
-> Maybe UpdateProgress
-> Int
-> DescribeDeviceJobResponse
DescribeDeviceJobResponse'
            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
"CreatedTime")
            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
"DeviceArn")
            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
"DeviceId")
            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
"DeviceName")
            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
"DeviceType")
            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
"ImageVersion")
            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
"JobId")
            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
"JobType")
            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 DescribeDeviceJob where
  hashWithSalt :: Int -> DescribeDeviceJob -> Int
hashWithSalt Int
_salt DescribeDeviceJob' {Text
jobId :: Text
$sel:jobId:DescribeDeviceJob' :: DescribeDeviceJob -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

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

instance Data.ToHeaders DescribeDeviceJob where
  toHeaders :: DescribeDeviceJob -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath DescribeDeviceJob where
  toPath :: DescribeDeviceJob -> ByteString
toPath DescribeDeviceJob' {Text
jobId :: Text
$sel:jobId:DescribeDeviceJob' :: DescribeDeviceJob -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/jobs/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
jobId]

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

-- | /See:/ 'newDescribeDeviceJobResponse' smart constructor.
data DescribeDeviceJobResponse = DescribeDeviceJobResponse'
  { -- | When the job was created.
    DescribeDeviceJobResponse -> Maybe POSIX
createdTime :: Prelude.Maybe Data.POSIX,
    -- | The device\'s ARN.
    DescribeDeviceJobResponse -> Maybe Text
deviceArn :: Prelude.Maybe Prelude.Text,
    -- | The device\'s ID.
    DescribeDeviceJobResponse -> Maybe Text
deviceId :: Prelude.Maybe Prelude.Text,
    -- | The device\'s name.
    DescribeDeviceJobResponse -> Maybe Text
deviceName :: Prelude.Maybe Prelude.Text,
    -- | The device\'s type.
    DescribeDeviceJobResponse -> Maybe DeviceType
deviceType :: Prelude.Maybe DeviceType,
    -- | For an OTA job, the target version of the device software.
    DescribeDeviceJobResponse -> Maybe Text
imageVersion :: Prelude.Maybe Prelude.Text,
    -- | The job\'s ID.
    DescribeDeviceJobResponse -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | The job\'s type.
    DescribeDeviceJobResponse -> Maybe JobType
jobType :: Prelude.Maybe JobType,
    -- | The job\'s status.
    DescribeDeviceJobResponse -> Maybe UpdateProgress
status :: Prelude.Maybe UpdateProgress,
    -- | The response's http status code.
    DescribeDeviceJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeDeviceJobResponse -> DescribeDeviceJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDeviceJobResponse -> DescribeDeviceJobResponse -> Bool
$c/= :: DescribeDeviceJobResponse -> DescribeDeviceJobResponse -> Bool
== :: DescribeDeviceJobResponse -> DescribeDeviceJobResponse -> Bool
$c== :: DescribeDeviceJobResponse -> DescribeDeviceJobResponse -> Bool
Prelude.Eq, ReadPrec [DescribeDeviceJobResponse]
ReadPrec DescribeDeviceJobResponse
Int -> ReadS DescribeDeviceJobResponse
ReadS [DescribeDeviceJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDeviceJobResponse]
$creadListPrec :: ReadPrec [DescribeDeviceJobResponse]
readPrec :: ReadPrec DescribeDeviceJobResponse
$creadPrec :: ReadPrec DescribeDeviceJobResponse
readList :: ReadS [DescribeDeviceJobResponse]
$creadList :: ReadS [DescribeDeviceJobResponse]
readsPrec :: Int -> ReadS DescribeDeviceJobResponse
$creadsPrec :: Int -> ReadS DescribeDeviceJobResponse
Prelude.Read, Int -> DescribeDeviceJobResponse -> ShowS
[DescribeDeviceJobResponse] -> ShowS
DescribeDeviceJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDeviceJobResponse] -> ShowS
$cshowList :: [DescribeDeviceJobResponse] -> ShowS
show :: DescribeDeviceJobResponse -> String
$cshow :: DescribeDeviceJobResponse -> String
showsPrec :: Int -> DescribeDeviceJobResponse -> ShowS
$cshowsPrec :: Int -> DescribeDeviceJobResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeDeviceJobResponse x -> DescribeDeviceJobResponse
forall x.
DescribeDeviceJobResponse -> Rep DescribeDeviceJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeDeviceJobResponse x -> DescribeDeviceJobResponse
$cfrom :: forall x.
DescribeDeviceJobResponse -> Rep DescribeDeviceJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDeviceJobResponse' 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:
--
-- 'createdTime', 'describeDeviceJobResponse_createdTime' - When the job was created.
--
-- 'deviceArn', 'describeDeviceJobResponse_deviceArn' - The device\'s ARN.
--
-- 'deviceId', 'describeDeviceJobResponse_deviceId' - The device\'s ID.
--
-- 'deviceName', 'describeDeviceJobResponse_deviceName' - The device\'s name.
--
-- 'deviceType', 'describeDeviceJobResponse_deviceType' - The device\'s type.
--
-- 'imageVersion', 'describeDeviceJobResponse_imageVersion' - For an OTA job, the target version of the device software.
--
-- 'jobId', 'describeDeviceJobResponse_jobId' - The job\'s ID.
--
-- 'jobType', 'describeDeviceJobResponse_jobType' - The job\'s type.
--
-- 'status', 'describeDeviceJobResponse_status' - The job\'s status.
--
-- 'httpStatus', 'describeDeviceJobResponse_httpStatus' - The response's http status code.
newDescribeDeviceJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeDeviceJobResponse
newDescribeDeviceJobResponse :: Int -> DescribeDeviceJobResponse
newDescribeDeviceJobResponse Int
pHttpStatus_ =
  DescribeDeviceJobResponse'
    { $sel:createdTime:DescribeDeviceJobResponse' :: Maybe POSIX
createdTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:deviceArn:DescribeDeviceJobResponse' :: Maybe Text
deviceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:deviceId:DescribeDeviceJobResponse' :: Maybe Text
deviceId = forall a. Maybe a
Prelude.Nothing,
      $sel:deviceName:DescribeDeviceJobResponse' :: Maybe Text
deviceName = forall a. Maybe a
Prelude.Nothing,
      $sel:deviceType:DescribeDeviceJobResponse' :: Maybe DeviceType
deviceType = forall a. Maybe a
Prelude.Nothing,
      $sel:imageVersion:DescribeDeviceJobResponse' :: Maybe Text
imageVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:DescribeDeviceJobResponse' :: Maybe Text
jobId = forall a. Maybe a
Prelude.Nothing,
      $sel:jobType:DescribeDeviceJobResponse' :: Maybe JobType
jobType = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DescribeDeviceJobResponse' :: Maybe UpdateProgress
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeDeviceJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | When the job was created.
describeDeviceJobResponse_createdTime :: Lens.Lens' DescribeDeviceJobResponse (Prelude.Maybe Prelude.UTCTime)
describeDeviceJobResponse_createdTime :: Lens' DescribeDeviceJobResponse (Maybe UTCTime)
describeDeviceJobResponse_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDeviceJobResponse' {Maybe POSIX
createdTime :: Maybe POSIX
$sel:createdTime:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe POSIX
createdTime} -> Maybe POSIX
createdTime) (\s :: DescribeDeviceJobResponse
s@DescribeDeviceJobResponse' {} Maybe POSIX
a -> DescribeDeviceJobResponse
s {$sel:createdTime:DescribeDeviceJobResponse' :: Maybe POSIX
createdTime = Maybe POSIX
a} :: DescribeDeviceJobResponse) 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

-- | The device\'s ARN.
describeDeviceJobResponse_deviceArn :: Lens.Lens' DescribeDeviceJobResponse (Prelude.Maybe Prelude.Text)
describeDeviceJobResponse_deviceArn :: Lens' DescribeDeviceJobResponse (Maybe Text)
describeDeviceJobResponse_deviceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDeviceJobResponse' {Maybe Text
deviceArn :: Maybe Text
$sel:deviceArn:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe Text
deviceArn} -> Maybe Text
deviceArn) (\s :: DescribeDeviceJobResponse
s@DescribeDeviceJobResponse' {} Maybe Text
a -> DescribeDeviceJobResponse
s {$sel:deviceArn:DescribeDeviceJobResponse' :: Maybe Text
deviceArn = Maybe Text
a} :: DescribeDeviceJobResponse)

-- | The device\'s ID.
describeDeviceJobResponse_deviceId :: Lens.Lens' DescribeDeviceJobResponse (Prelude.Maybe Prelude.Text)
describeDeviceJobResponse_deviceId :: Lens' DescribeDeviceJobResponse (Maybe Text)
describeDeviceJobResponse_deviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDeviceJobResponse' {Maybe Text
deviceId :: Maybe Text
$sel:deviceId:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe Text
deviceId} -> Maybe Text
deviceId) (\s :: DescribeDeviceJobResponse
s@DescribeDeviceJobResponse' {} Maybe Text
a -> DescribeDeviceJobResponse
s {$sel:deviceId:DescribeDeviceJobResponse' :: Maybe Text
deviceId = Maybe Text
a} :: DescribeDeviceJobResponse)

-- | The device\'s name.
describeDeviceJobResponse_deviceName :: Lens.Lens' DescribeDeviceJobResponse (Prelude.Maybe Prelude.Text)
describeDeviceJobResponse_deviceName :: Lens' DescribeDeviceJobResponse (Maybe Text)
describeDeviceJobResponse_deviceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDeviceJobResponse' {Maybe Text
deviceName :: Maybe Text
$sel:deviceName:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe Text
deviceName} -> Maybe Text
deviceName) (\s :: DescribeDeviceJobResponse
s@DescribeDeviceJobResponse' {} Maybe Text
a -> DescribeDeviceJobResponse
s {$sel:deviceName:DescribeDeviceJobResponse' :: Maybe Text
deviceName = Maybe Text
a} :: DescribeDeviceJobResponse)

-- | The device\'s type.
describeDeviceJobResponse_deviceType :: Lens.Lens' DescribeDeviceJobResponse (Prelude.Maybe DeviceType)
describeDeviceJobResponse_deviceType :: Lens' DescribeDeviceJobResponse (Maybe DeviceType)
describeDeviceJobResponse_deviceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDeviceJobResponse' {Maybe DeviceType
deviceType :: Maybe DeviceType
$sel:deviceType:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe DeviceType
deviceType} -> Maybe DeviceType
deviceType) (\s :: DescribeDeviceJobResponse
s@DescribeDeviceJobResponse' {} Maybe DeviceType
a -> DescribeDeviceJobResponse
s {$sel:deviceType:DescribeDeviceJobResponse' :: Maybe DeviceType
deviceType = Maybe DeviceType
a} :: DescribeDeviceJobResponse)

-- | For an OTA job, the target version of the device software.
describeDeviceJobResponse_imageVersion :: Lens.Lens' DescribeDeviceJobResponse (Prelude.Maybe Prelude.Text)
describeDeviceJobResponse_imageVersion :: Lens' DescribeDeviceJobResponse (Maybe Text)
describeDeviceJobResponse_imageVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDeviceJobResponse' {Maybe Text
imageVersion :: Maybe Text
$sel:imageVersion:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe Text
imageVersion} -> Maybe Text
imageVersion) (\s :: DescribeDeviceJobResponse
s@DescribeDeviceJobResponse' {} Maybe Text
a -> DescribeDeviceJobResponse
s {$sel:imageVersion:DescribeDeviceJobResponse' :: Maybe Text
imageVersion = Maybe Text
a} :: DescribeDeviceJobResponse)

-- | The job\'s ID.
describeDeviceJobResponse_jobId :: Lens.Lens' DescribeDeviceJobResponse (Prelude.Maybe Prelude.Text)
describeDeviceJobResponse_jobId :: Lens' DescribeDeviceJobResponse (Maybe Text)
describeDeviceJobResponse_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDeviceJobResponse' {Maybe Text
jobId :: Maybe Text
$sel:jobId:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: DescribeDeviceJobResponse
s@DescribeDeviceJobResponse' {} Maybe Text
a -> DescribeDeviceJobResponse
s {$sel:jobId:DescribeDeviceJobResponse' :: Maybe Text
jobId = Maybe Text
a} :: DescribeDeviceJobResponse)

-- | The job\'s type.
describeDeviceJobResponse_jobType :: Lens.Lens' DescribeDeviceJobResponse (Prelude.Maybe JobType)
describeDeviceJobResponse_jobType :: Lens' DescribeDeviceJobResponse (Maybe JobType)
describeDeviceJobResponse_jobType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDeviceJobResponse' {Maybe JobType
jobType :: Maybe JobType
$sel:jobType:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe JobType
jobType} -> Maybe JobType
jobType) (\s :: DescribeDeviceJobResponse
s@DescribeDeviceJobResponse' {} Maybe JobType
a -> DescribeDeviceJobResponse
s {$sel:jobType:DescribeDeviceJobResponse' :: Maybe JobType
jobType = Maybe JobType
a} :: DescribeDeviceJobResponse)

-- | The job\'s status.
describeDeviceJobResponse_status :: Lens.Lens' DescribeDeviceJobResponse (Prelude.Maybe UpdateProgress)
describeDeviceJobResponse_status :: Lens' DescribeDeviceJobResponse (Maybe UpdateProgress)
describeDeviceJobResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDeviceJobResponse' {Maybe UpdateProgress
status :: Maybe UpdateProgress
$sel:status:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe UpdateProgress
status} -> Maybe UpdateProgress
status) (\s :: DescribeDeviceJobResponse
s@DescribeDeviceJobResponse' {} Maybe UpdateProgress
a -> DescribeDeviceJobResponse
s {$sel:status:DescribeDeviceJobResponse' :: Maybe UpdateProgress
status = Maybe UpdateProgress
a} :: DescribeDeviceJobResponse)

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

instance Prelude.NFData DescribeDeviceJobResponse where
  rnf :: DescribeDeviceJobResponse -> ()
rnf DescribeDeviceJobResponse' {Int
Maybe Text
Maybe POSIX
Maybe DeviceType
Maybe JobType
Maybe UpdateProgress
httpStatus :: Int
status :: Maybe UpdateProgress
jobType :: Maybe JobType
jobId :: Maybe Text
imageVersion :: Maybe Text
deviceType :: Maybe DeviceType
deviceName :: Maybe Text
deviceId :: Maybe Text
deviceArn :: Maybe Text
createdTime :: Maybe POSIX
$sel:httpStatus:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Int
$sel:status:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe UpdateProgress
$sel:jobType:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe JobType
$sel:jobId:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe Text
$sel:imageVersion:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe Text
$sel:deviceType:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe DeviceType
$sel:deviceName:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe Text
$sel:deviceId:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe Text
$sel:deviceArn:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe Text
$sel:createdTime:DescribeDeviceJobResponse' :: DescribeDeviceJobResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deviceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deviceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deviceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeviceType
deviceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
imageVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobType
jobType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UpdateProgress
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus