{-# 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.Snowball.GetJobManifest
-- 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 a link to an Amazon S3 presigned URL for the manifest file
-- associated with the specified @JobId@ value. You can access the manifest
-- file for up to 60 minutes after this request has been made. To access
-- the manifest file after 60 minutes have passed, you\'ll have to make
-- another call to the @GetJobManifest@ action.
--
-- The manifest is an encrypted file that you can download after your job
-- enters the @WithCustomer@ status. This is the only valid status for
-- calling this API as the manifest and @UnlockCode@ code value are used
-- for securing your device and should only be used when you have the
-- device. The manifest is decrypted by using the @UnlockCode@ code value,
-- when you pass both values to the Snow device through the Snowball client
-- when the client is started for the first time.
--
-- As a best practice, we recommend that you don\'t save a copy of an
-- @UnlockCode@ value in the same location as the manifest file for that
-- job. Saving these separately helps prevent unauthorized parties from
-- gaining access to the Snow device associated with that job.
--
-- The credentials of a given job, including its manifest file and unlock
-- code, expire 360 days after the job is created.
module Amazonka.Snowball.GetJobManifest
  ( -- * Creating a Request
    GetJobManifest (..),
    newGetJobManifest,

    -- * Request Lenses
    getJobManifest_jobId,

    -- * Destructuring the Response
    GetJobManifestResponse (..),
    newGetJobManifestResponse,

    -- * Response Lenses
    getJobManifestResponse_manifestURI,
    getJobManifestResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetJobManifest' smart constructor.
data GetJobManifest = GetJobManifest'
  { -- | The ID for a job that you want to get the manifest file for, for example
    -- @JID123e4567-e89b-12d3-a456-426655440000@.
    GetJobManifest -> Text
jobId :: Prelude.Text
  }
  deriving (GetJobManifest -> GetJobManifest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetJobManifest -> GetJobManifest -> Bool
$c/= :: GetJobManifest -> GetJobManifest -> Bool
== :: GetJobManifest -> GetJobManifest -> Bool
$c== :: GetJobManifest -> GetJobManifest -> Bool
Prelude.Eq, ReadPrec [GetJobManifest]
ReadPrec GetJobManifest
Int -> ReadS GetJobManifest
ReadS [GetJobManifest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetJobManifest]
$creadListPrec :: ReadPrec [GetJobManifest]
readPrec :: ReadPrec GetJobManifest
$creadPrec :: ReadPrec GetJobManifest
readList :: ReadS [GetJobManifest]
$creadList :: ReadS [GetJobManifest]
readsPrec :: Int -> ReadS GetJobManifest
$creadsPrec :: Int -> ReadS GetJobManifest
Prelude.Read, Int -> GetJobManifest -> ShowS
[GetJobManifest] -> ShowS
GetJobManifest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetJobManifest] -> ShowS
$cshowList :: [GetJobManifest] -> ShowS
show :: GetJobManifest -> String
$cshow :: GetJobManifest -> String
showsPrec :: Int -> GetJobManifest -> ShowS
$cshowsPrec :: Int -> GetJobManifest -> ShowS
Prelude.Show, forall x. Rep GetJobManifest x -> GetJobManifest
forall x. GetJobManifest -> Rep GetJobManifest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetJobManifest x -> GetJobManifest
$cfrom :: forall x. GetJobManifest -> Rep GetJobManifest x
Prelude.Generic)

-- |
-- Create a value of 'GetJobManifest' 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', 'getJobManifest_jobId' - The ID for a job that you want to get the manifest file for, for example
-- @JID123e4567-e89b-12d3-a456-426655440000@.
newGetJobManifest ::
  -- | 'jobId'
  Prelude.Text ->
  GetJobManifest
newGetJobManifest :: Text -> GetJobManifest
newGetJobManifest Text
pJobId_ =
  GetJobManifest' {$sel:jobId:GetJobManifest' :: Text
jobId = Text
pJobId_}

-- | The ID for a job that you want to get the manifest file for, for example
-- @JID123e4567-e89b-12d3-a456-426655440000@.
getJobManifest_jobId :: Lens.Lens' GetJobManifest Prelude.Text
getJobManifest_jobId :: Lens' GetJobManifest Text
getJobManifest_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobManifest' {Text
jobId :: Text
$sel:jobId:GetJobManifest' :: GetJobManifest -> Text
jobId} -> Text
jobId) (\s :: GetJobManifest
s@GetJobManifest' {} Text
a -> GetJobManifest
s {$sel:jobId:GetJobManifest' :: Text
jobId = Text
a} :: GetJobManifest)

instance Core.AWSRequest GetJobManifest where
  type
    AWSResponse GetJobManifest =
      GetJobManifestResponse
  request :: (Service -> Service) -> GetJobManifest -> Request GetJobManifest
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetJobManifest
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetJobManifest)))
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 -> GetJobManifestResponse
GetJobManifestResponse'
            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
"ManifestURI")
            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 GetJobManifest where
  hashWithSalt :: Int -> GetJobManifest -> Int
hashWithSalt Int
_salt GetJobManifest' {Text
jobId :: Text
$sel:jobId:GetJobManifest' :: GetJobManifest -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

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

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

instance Data.ToJSON GetJobManifest where
  toJSON :: GetJobManifest -> Value
toJSON GetJobManifest' {Text
jobId :: Text
$sel:jobId:GetJobManifest' :: GetJobManifest -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"JobId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
jobId)]
      )

instance Data.ToPath GetJobManifest where
  toPath :: GetJobManifest -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetJobManifestResponse' smart constructor.
data GetJobManifestResponse = GetJobManifestResponse'
  { -- | The Amazon S3 presigned URL for the manifest file associated with the
    -- specified @JobId@ value.
    GetJobManifestResponse -> Maybe Text
manifestURI :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetJobManifestResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetJobManifestResponse -> GetJobManifestResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetJobManifestResponse -> GetJobManifestResponse -> Bool
$c/= :: GetJobManifestResponse -> GetJobManifestResponse -> Bool
== :: GetJobManifestResponse -> GetJobManifestResponse -> Bool
$c== :: GetJobManifestResponse -> GetJobManifestResponse -> Bool
Prelude.Eq, ReadPrec [GetJobManifestResponse]
ReadPrec GetJobManifestResponse
Int -> ReadS GetJobManifestResponse
ReadS [GetJobManifestResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetJobManifestResponse]
$creadListPrec :: ReadPrec [GetJobManifestResponse]
readPrec :: ReadPrec GetJobManifestResponse
$creadPrec :: ReadPrec GetJobManifestResponse
readList :: ReadS [GetJobManifestResponse]
$creadList :: ReadS [GetJobManifestResponse]
readsPrec :: Int -> ReadS GetJobManifestResponse
$creadsPrec :: Int -> ReadS GetJobManifestResponse
Prelude.Read, Int -> GetJobManifestResponse -> ShowS
[GetJobManifestResponse] -> ShowS
GetJobManifestResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetJobManifestResponse] -> ShowS
$cshowList :: [GetJobManifestResponse] -> ShowS
show :: GetJobManifestResponse -> String
$cshow :: GetJobManifestResponse -> String
showsPrec :: Int -> GetJobManifestResponse -> ShowS
$cshowsPrec :: Int -> GetJobManifestResponse -> ShowS
Prelude.Show, forall x. Rep GetJobManifestResponse x -> GetJobManifestResponse
forall x. GetJobManifestResponse -> Rep GetJobManifestResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetJobManifestResponse x -> GetJobManifestResponse
$cfrom :: forall x. GetJobManifestResponse -> Rep GetJobManifestResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetJobManifestResponse' 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:
--
-- 'manifestURI', 'getJobManifestResponse_manifestURI' - The Amazon S3 presigned URL for the manifest file associated with the
-- specified @JobId@ value.
--
-- 'httpStatus', 'getJobManifestResponse_httpStatus' - The response's http status code.
newGetJobManifestResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetJobManifestResponse
newGetJobManifestResponse :: Int -> GetJobManifestResponse
newGetJobManifestResponse Int
pHttpStatus_ =
  GetJobManifestResponse'
    { $sel:manifestURI:GetJobManifestResponse' :: Maybe Text
manifestURI =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetJobManifestResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon S3 presigned URL for the manifest file associated with the
-- specified @JobId@ value.
getJobManifestResponse_manifestURI :: Lens.Lens' GetJobManifestResponse (Prelude.Maybe Prelude.Text)
getJobManifestResponse_manifestURI :: Lens' GetJobManifestResponse (Maybe Text)
getJobManifestResponse_manifestURI = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobManifestResponse' {Maybe Text
manifestURI :: Maybe Text
$sel:manifestURI:GetJobManifestResponse' :: GetJobManifestResponse -> Maybe Text
manifestURI} -> Maybe Text
manifestURI) (\s :: GetJobManifestResponse
s@GetJobManifestResponse' {} Maybe Text
a -> GetJobManifestResponse
s {$sel:manifestURI:GetJobManifestResponse' :: Maybe Text
manifestURI = Maybe Text
a} :: GetJobManifestResponse)

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

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