{-# 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.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)
--
-- Returns information about a specific job including shipping information,
-- job status, and other important metadata.
module Amazonka.Snowball.DescribeJob
  ( -- * Creating a Request
    DescribeJob (..),
    newDescribeJob,

    -- * Request Lenses
    describeJob_jobId,

    -- * Destructuring the Response
    DescribeJobResponse (..),
    newDescribeJobResponse,

    -- * Response Lenses
    describeJobResponse_jobMetadata,
    describeJobResponse_subJobMetadata,
    describeJobResponse_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:/ 'newDescribeJob' smart constructor.
data DescribeJob = DescribeJob'
  { -- | The automatically generated ID for a job, for example
    -- @JID123e4567-e89b-12d3-a456-426655440000@.
    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:
--
-- 'jobId', 'describeJob_jobId' - The automatically generated ID for a job, for example
-- @JID123e4567-e89b-12d3-a456-426655440000@.
newDescribeJob ::
  -- | 'jobId'
  Prelude.Text ->
  DescribeJob
newDescribeJob :: Text -> DescribeJob
newDescribeJob Text
pJobId_ =
  DescribeJob' {$sel:jobId:DescribeJob' :: Text
jobId = Text
pJobId_}

-- | The automatically generated ID for a job, for example
-- @JID123e4567-e89b-12d3-a456-426655440000@.
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 = DescribeJobResponse
  request :: (Service -> Service) -> DescribeJob -> Request DescribeJob
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 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 ->
          Maybe JobMetadata
-> Maybe [JobMetadata] -> Int -> DescribeJobResponse
DescribeJobResponse'
            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
"JobMetadata")
            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
"SubJobMetadata" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 DescribeJob where
  hashWithSalt :: Int -> DescribeJob -> Int
hashWithSalt Int
_salt DescribeJob' {Text
jobId :: Text
$sel:jobId:DescribeJob' :: DescribeJob -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

instance Prelude.NFData DescribeJob where
  rnf :: DescribeJob -> ()
rnf DescribeJob' {Text
jobId :: Text
$sel:jobId:DescribeJob' :: DescribeJob -> Text
..} = 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] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSIESnowballJobManagementService.DescribeJob" ::
                          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 DescribeJob where
  toJSON :: DescribeJob -> Value
toJSON DescribeJob' {Text
jobId :: Text
$sel:jobId:DescribeJob' :: DescribeJob -> 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 DescribeJob where
  toPath :: DescribeJob -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDescribeJobResponse' smart constructor.
data DescribeJobResponse = DescribeJobResponse'
  { -- | Information about a specific job, including shipping information, job
    -- status, and other important metadata.
    DescribeJobResponse -> Maybe JobMetadata
jobMetadata :: Prelude.Maybe JobMetadata,
    -- | Information about a specific job part (in the case of an export job),
    -- including shipping information, job status, and other important
    -- metadata.
    DescribeJobResponse -> Maybe [JobMetadata]
subJobMetadata :: Prelude.Maybe [JobMetadata],
    -- | The response's http status code.
    DescribeJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeJobResponse -> DescribeJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeJobResponse -> DescribeJobResponse -> Bool
$c/= :: DescribeJobResponse -> DescribeJobResponse -> Bool
== :: DescribeJobResponse -> DescribeJobResponse -> Bool
$c== :: DescribeJobResponse -> DescribeJobResponse -> Bool
Prelude.Eq, ReadPrec [DescribeJobResponse]
ReadPrec DescribeJobResponse
Int -> ReadS DescribeJobResponse
ReadS [DescribeJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeJobResponse]
$creadListPrec :: ReadPrec [DescribeJobResponse]
readPrec :: ReadPrec DescribeJobResponse
$creadPrec :: ReadPrec DescribeJobResponse
readList :: ReadS [DescribeJobResponse]
$creadList :: ReadS [DescribeJobResponse]
readsPrec :: Int -> ReadS DescribeJobResponse
$creadsPrec :: Int -> ReadS DescribeJobResponse
Prelude.Read, Int -> DescribeJobResponse -> ShowS
[DescribeJobResponse] -> ShowS
DescribeJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeJobResponse] -> ShowS
$cshowList :: [DescribeJobResponse] -> ShowS
show :: DescribeJobResponse -> String
$cshow :: DescribeJobResponse -> String
showsPrec :: Int -> DescribeJobResponse -> ShowS
$cshowsPrec :: Int -> DescribeJobResponse -> ShowS
Prelude.Show, forall x. Rep DescribeJobResponse x -> DescribeJobResponse
forall x. DescribeJobResponse -> Rep DescribeJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeJobResponse x -> DescribeJobResponse
$cfrom :: forall x. DescribeJobResponse -> Rep DescribeJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeJobResponse' 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:
--
-- 'jobMetadata', 'describeJobResponse_jobMetadata' - Information about a specific job, including shipping information, job
-- status, and other important metadata.
--
-- 'subJobMetadata', 'describeJobResponse_subJobMetadata' - Information about a specific job part (in the case of an export job),
-- including shipping information, job status, and other important
-- metadata.
--
-- 'httpStatus', 'describeJobResponse_httpStatus' - The response's http status code.
newDescribeJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeJobResponse
newDescribeJobResponse :: Int -> DescribeJobResponse
newDescribeJobResponse Int
pHttpStatus_ =
  DescribeJobResponse'
    { $sel:jobMetadata:DescribeJobResponse' :: Maybe JobMetadata
jobMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:subJobMetadata:DescribeJobResponse' :: Maybe [JobMetadata]
subJobMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about a specific job, including shipping information, job
-- status, and other important metadata.
describeJobResponse_jobMetadata :: Lens.Lens' DescribeJobResponse (Prelude.Maybe JobMetadata)
describeJobResponse_jobMetadata :: Lens' DescribeJobResponse (Maybe JobMetadata)
describeJobResponse_jobMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobResponse' {Maybe JobMetadata
jobMetadata :: Maybe JobMetadata
$sel:jobMetadata:DescribeJobResponse' :: DescribeJobResponse -> Maybe JobMetadata
jobMetadata} -> Maybe JobMetadata
jobMetadata) (\s :: DescribeJobResponse
s@DescribeJobResponse' {} Maybe JobMetadata
a -> DescribeJobResponse
s {$sel:jobMetadata:DescribeJobResponse' :: Maybe JobMetadata
jobMetadata = Maybe JobMetadata
a} :: DescribeJobResponse)

-- | Information about a specific job part (in the case of an export job),
-- including shipping information, job status, and other important
-- metadata.
describeJobResponse_subJobMetadata :: Lens.Lens' DescribeJobResponse (Prelude.Maybe [JobMetadata])
describeJobResponse_subJobMetadata :: Lens' DescribeJobResponse (Maybe [JobMetadata])
describeJobResponse_subJobMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobResponse' {Maybe [JobMetadata]
subJobMetadata :: Maybe [JobMetadata]
$sel:subJobMetadata:DescribeJobResponse' :: DescribeJobResponse -> Maybe [JobMetadata]
subJobMetadata} -> Maybe [JobMetadata]
subJobMetadata) (\s :: DescribeJobResponse
s@DescribeJobResponse' {} Maybe [JobMetadata]
a -> DescribeJobResponse
s {$sel:subJobMetadata:DescribeJobResponse' :: Maybe [JobMetadata]
subJobMetadata = Maybe [JobMetadata]
a} :: DescribeJobResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData DescribeJobResponse where
  rnf :: DescribeJobResponse -> ()
rnf DescribeJobResponse' {Int
Maybe [JobMetadata]
Maybe JobMetadata
httpStatus :: Int
subJobMetadata :: Maybe [JobMetadata]
jobMetadata :: Maybe JobMetadata
$sel:httpStatus:DescribeJobResponse' :: DescribeJobResponse -> Int
$sel:subJobMetadata:DescribeJobResponse' :: DescribeJobResponse -> Maybe [JobMetadata]
$sel:jobMetadata:DescribeJobResponse' :: DescribeJobResponse -> Maybe JobMetadata
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe JobMetadata
jobMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [JobMetadata]
subJobMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus