{-# 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.IoT.GetJobDocument
-- 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 a job document.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions GetJobDocument>
-- action.
module Amazonka.IoT.GetJobDocument
  ( -- * Creating a Request
    GetJobDocument (..),
    newGetJobDocument,

    -- * Request Lenses
    getJobDocument_jobId,

    -- * Destructuring the Response
    GetJobDocumentResponse (..),
    newGetJobDocumentResponse,

    -- * Response Lenses
    getJobDocumentResponse_document,
    getJobDocumentResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetJobDocument' smart constructor.
data GetJobDocument = GetJobDocument'
  { -- | The unique identifier you assigned to this job when it was created.
    GetJobDocument -> Text
jobId :: Prelude.Text
  }
  deriving (GetJobDocument -> GetJobDocument -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetJobDocument -> GetJobDocument -> Bool
$c/= :: GetJobDocument -> GetJobDocument -> Bool
== :: GetJobDocument -> GetJobDocument -> Bool
$c== :: GetJobDocument -> GetJobDocument -> Bool
Prelude.Eq, ReadPrec [GetJobDocument]
ReadPrec GetJobDocument
Int -> ReadS GetJobDocument
ReadS [GetJobDocument]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetJobDocument]
$creadListPrec :: ReadPrec [GetJobDocument]
readPrec :: ReadPrec GetJobDocument
$creadPrec :: ReadPrec GetJobDocument
readList :: ReadS [GetJobDocument]
$creadList :: ReadS [GetJobDocument]
readsPrec :: Int -> ReadS GetJobDocument
$creadsPrec :: Int -> ReadS GetJobDocument
Prelude.Read, Int -> GetJobDocument -> ShowS
[GetJobDocument] -> ShowS
GetJobDocument -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetJobDocument] -> ShowS
$cshowList :: [GetJobDocument] -> ShowS
show :: GetJobDocument -> String
$cshow :: GetJobDocument -> String
showsPrec :: Int -> GetJobDocument -> ShowS
$cshowsPrec :: Int -> GetJobDocument -> ShowS
Prelude.Show, forall x. Rep GetJobDocument x -> GetJobDocument
forall x. GetJobDocument -> Rep GetJobDocument x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetJobDocument x -> GetJobDocument
$cfrom :: forall x. GetJobDocument -> Rep GetJobDocument x
Prelude.Generic)

-- |
-- Create a value of 'GetJobDocument' 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', 'getJobDocument_jobId' - The unique identifier you assigned to this job when it was created.
newGetJobDocument ::
  -- | 'jobId'
  Prelude.Text ->
  GetJobDocument
newGetJobDocument :: Text -> GetJobDocument
newGetJobDocument Text
pJobId_ =
  GetJobDocument' {$sel:jobId:GetJobDocument' :: Text
jobId = Text
pJobId_}

-- | The unique identifier you assigned to this job when it was created.
getJobDocument_jobId :: Lens.Lens' GetJobDocument Prelude.Text
getJobDocument_jobId :: Lens' GetJobDocument Text
getJobDocument_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobDocument' {Text
jobId :: Text
$sel:jobId:GetJobDocument' :: GetJobDocument -> Text
jobId} -> Text
jobId) (\s :: GetJobDocument
s@GetJobDocument' {} Text
a -> GetJobDocument
s {$sel:jobId:GetJobDocument' :: Text
jobId = Text
a} :: GetJobDocument)

instance Core.AWSRequest GetJobDocument where
  type
    AWSResponse GetJobDocument =
      GetJobDocumentResponse
  request :: (Service -> Service) -> GetJobDocument -> Request GetJobDocument
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 GetJobDocument
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetJobDocument)))
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 -> Int -> GetJobDocumentResponse
GetJobDocumentResponse'
            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
"document")
            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 GetJobDocument where
  hashWithSalt :: Int -> GetJobDocument -> Int
hashWithSalt Int
_salt GetJobDocument' {Text
jobId :: Text
$sel:jobId:GetJobDocument' :: GetJobDocument -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

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

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

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

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

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

-- |
-- Create a value of 'GetJobDocumentResponse' 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:
--
-- 'document', 'getJobDocumentResponse_document' - The job document content.
--
-- 'httpStatus', 'getJobDocumentResponse_httpStatus' - The response's http status code.
newGetJobDocumentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetJobDocumentResponse
newGetJobDocumentResponse :: Int -> GetJobDocumentResponse
newGetJobDocumentResponse Int
pHttpStatus_ =
  GetJobDocumentResponse'
    { $sel:document:GetJobDocumentResponse' :: Maybe Text
document = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetJobDocumentResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The job document content.
getJobDocumentResponse_document :: Lens.Lens' GetJobDocumentResponse (Prelude.Maybe Prelude.Text)
getJobDocumentResponse_document :: Lens' GetJobDocumentResponse (Maybe Text)
getJobDocumentResponse_document = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobDocumentResponse' {Maybe Text
document :: Maybe Text
$sel:document:GetJobDocumentResponse' :: GetJobDocumentResponse -> Maybe Text
document} -> Maybe Text
document) (\s :: GetJobDocumentResponse
s@GetJobDocumentResponse' {} Maybe Text
a -> GetJobDocumentResponse
s {$sel:document:GetJobDocumentResponse' :: Maybe Text
document = Maybe Text
a} :: GetJobDocumentResponse)

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

instance Prelude.NFData GetJobDocumentResponse where
  rnf :: GetJobDocumentResponse -> ()
rnf GetJobDocumentResponse' {Int
Maybe Text
httpStatus :: Int
document :: Maybe Text
$sel:httpStatus:GetJobDocumentResponse' :: GetJobDocumentResponse -> Int
$sel:document:GetJobDocumentResponse' :: GetJobDocumentResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
document
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus