{-# 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.Glacier.DescribeJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This operation returns information about a job you previously initiated,
-- including the job initiation date, the user who initiated the job, the
-- job status code\/message and the Amazon SNS topic to notify after Amazon
-- S3 Glacier (Glacier) completes the job. For more information about
-- initiating a job, see InitiateJob.
--
-- This operation enables you to check the status of your job. However, it
-- is strongly recommended that you set up an Amazon SNS topic and specify
-- it in your initiate job request so that Glacier can notify the topic
-- after it completes the job.
--
-- A job ID will not expire for at least 24 hours after Glacier completes
-- the job.
--
-- An AWS account has full permission to perform all operations (actions).
-- However, AWS Identity and Access Management (IAM) users don\'t have any
-- permissions by default. You must grant them explicit permission to
-- perform specific actions. For more information, see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/using-iam-with-amazon-glacier.html Access Control Using AWS Identity and Access Management (IAM)>.
--
-- For more information about using this operation, see the documentation
-- for the underlying REST API
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/api-describe-job-get.html Describe Job>
-- in the /Amazon Glacier Developer Guide/.
module Amazonka.Glacier.DescribeJob
  ( -- * Creating a Request
    DescribeJob (..),
    newDescribeJob,

    -- * Request Lenses
    describeJob_accountId,
    describeJob_vaultName,
    describeJob_jobId,

    -- * Destructuring the Response
    GlacierJobDescription (..),
    newGlacierJobDescription,

    -- * Response Lenses
    glacierJobDescription_action,
    glacierJobDescription_archiveId,
    glacierJobDescription_archiveSHA256TreeHash,
    glacierJobDescription_archiveSizeInBytes,
    glacierJobDescription_completed,
    glacierJobDescription_completionDate,
    glacierJobDescription_creationDate,
    glacierJobDescription_inventoryRetrievalParameters,
    glacierJobDescription_inventorySizeInBytes,
    glacierJobDescription_jobDescription,
    glacierJobDescription_jobId,
    glacierJobDescription_jobOutputPath,
    glacierJobDescription_outputLocation,
    glacierJobDescription_retrievalByteRange,
    glacierJobDescription_sHA256TreeHash,
    glacierJobDescription_sNSTopic,
    glacierJobDescription_selectParameters,
    glacierJobDescription_statusCode,
    glacierJobDescription_statusMessage,
    glacierJobDescription_tier,
    glacierJobDescription_vaultARN,
  )
where

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

-- | Provides options for retrieving a job description.
--
-- /See:/ 'newDescribeJob' smart constructor.
data DescribeJob = DescribeJob'
  { -- | The @AccountId@ value is the AWS account ID of the account that owns the
    -- vault. You can either specify an AWS account ID or optionally a single
    -- \'@-@\' (hyphen), in which case Amazon S3 Glacier uses the AWS account
    -- ID associated with the credentials used to sign the request. If you use
    -- an account ID, do not include any hyphens (\'-\') in the ID.
    DescribeJob -> Text
accountId :: Prelude.Text,
    -- | The name of the vault.
    DescribeJob -> Text
vaultName :: Prelude.Text,
    -- | The ID of the job to describe.
    DescribeJob -> Text
jobId :: Prelude.Text
  }
  deriving (DescribeJob -> DescribeJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeJob -> DescribeJob -> Bool
$c/= :: DescribeJob -> DescribeJob -> Bool
== :: DescribeJob -> DescribeJob -> Bool
$c== :: DescribeJob -> DescribeJob -> Bool
Prelude.Eq, ReadPrec [DescribeJob]
ReadPrec DescribeJob
Int -> ReadS DescribeJob
ReadS [DescribeJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeJob]
$creadListPrec :: ReadPrec [DescribeJob]
readPrec :: ReadPrec DescribeJob
$creadPrec :: ReadPrec DescribeJob
readList :: ReadS [DescribeJob]
$creadList :: ReadS [DescribeJob]
readsPrec :: Int -> ReadS DescribeJob
$creadsPrec :: Int -> ReadS DescribeJob
Prelude.Read, Int -> DescribeJob -> ShowS
[DescribeJob] -> ShowS
DescribeJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeJob] -> ShowS
$cshowList :: [DescribeJob] -> ShowS
show :: DescribeJob -> String
$cshow :: DescribeJob -> String
showsPrec :: Int -> DescribeJob -> ShowS
$cshowsPrec :: Int -> DescribeJob -> ShowS
Prelude.Show, forall x. Rep DescribeJob x -> DescribeJob
forall x. DescribeJob -> Rep DescribeJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeJob x -> DescribeJob
$cfrom :: forall x. DescribeJob -> Rep DescribeJob x
Prelude.Generic)

-- |
-- Create a value of 'DescribeJob' 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:
--
-- 'accountId', 'describeJob_accountId' - The @AccountId@ value is the AWS account ID of the account that owns the
-- vault. You can either specify an AWS account ID or optionally a single
-- \'@-@\' (hyphen), in which case Amazon S3 Glacier uses the AWS account
-- ID associated with the credentials used to sign the request. If you use
-- an account ID, do not include any hyphens (\'-\') in the ID.
--
-- 'vaultName', 'describeJob_vaultName' - The name of the vault.
--
-- 'jobId', 'describeJob_jobId' - The ID of the job to describe.
newDescribeJob ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'vaultName'
  Prelude.Text ->
  -- | 'jobId'
  Prelude.Text ->
  DescribeJob
newDescribeJob :: Text -> Text -> Text -> DescribeJob
newDescribeJob Text
pAccountId_ Text
pVaultName_ Text
pJobId_ =
  DescribeJob'
    { $sel:accountId:DescribeJob' :: Text
accountId = Text
pAccountId_,
      $sel:vaultName:DescribeJob' :: Text
vaultName = Text
pVaultName_,
      $sel:jobId:DescribeJob' :: Text
jobId = Text
pJobId_
    }

-- | The @AccountId@ value is the AWS account ID of the account that owns the
-- vault. You can either specify an AWS account ID or optionally a single
-- \'@-@\' (hyphen), in which case Amazon S3 Glacier uses the AWS account
-- ID associated with the credentials used to sign the request. If you use
-- an account ID, do not include any hyphens (\'-\') in the ID.
describeJob_accountId :: Lens.Lens' DescribeJob Prelude.Text
describeJob_accountId :: Lens' DescribeJob Text
describeJob_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJob' {Text
accountId :: Text
$sel:accountId:DescribeJob' :: DescribeJob -> Text
accountId} -> Text
accountId) (\s :: DescribeJob
s@DescribeJob' {} Text
a -> DescribeJob
s {$sel:accountId:DescribeJob' :: Text
accountId = Text
a} :: DescribeJob)

-- | The name of the vault.
describeJob_vaultName :: Lens.Lens' DescribeJob Prelude.Text
describeJob_vaultName :: Lens' DescribeJob Text
describeJob_vaultName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJob' {Text
vaultName :: Text
$sel:vaultName:DescribeJob' :: DescribeJob -> Text
vaultName} -> Text
vaultName) (\s :: DescribeJob
s@DescribeJob' {} Text
a -> DescribeJob
s {$sel:vaultName:DescribeJob' :: Text
vaultName = Text
a} :: DescribeJob)

-- | The ID of the job to describe.
describeJob_jobId :: Lens.Lens' DescribeJob Prelude.Text
describeJob_jobId :: Lens' DescribeJob Text
describeJob_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJob' {Text
jobId :: Text
$sel:jobId:DescribeJob' :: DescribeJob -> Text
jobId} -> Text
jobId) (\s :: DescribeJob
s@DescribeJob' {} Text
a -> DescribeJob
s {$sel:jobId:DescribeJob' :: Text
jobId = Text
a} :: DescribeJob)

instance Core.AWSRequest DescribeJob where
  type AWSResponse DescribeJob = GlacierJobDescription
  request :: (Service -> Service) -> DescribeJob -> Request DescribeJob
request Service -> Service
overrides =
    forall a. ByteString -> Request a -> Request a
Request.glacierVersionHeader (Service -> ByteString
Core.version Service
defaultService)
      forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. 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 DescribeJob
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeJob)))
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 -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

instance Prelude.Hashable DescribeJob where
  hashWithSalt :: Int -> DescribeJob -> Int
hashWithSalt Int
_salt DescribeJob' {Text
jobId :: Text
vaultName :: Text
accountId :: Text
$sel:jobId:DescribeJob' :: DescribeJob -> Text
$sel:vaultName:DescribeJob' :: DescribeJob -> Text
$sel:accountId:DescribeJob' :: DescribeJob -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vaultName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

instance Prelude.NFData DescribeJob where
  rnf :: DescribeJob -> ()
rnf DescribeJob' {Text
jobId :: Text
vaultName :: Text
accountId :: Text
$sel:jobId:DescribeJob' :: DescribeJob -> Text
$sel:vaultName:DescribeJob' :: DescribeJob -> Text
$sel:accountId:DescribeJob' :: DescribeJob -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vaultName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobId

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

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

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