{-# 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.GetSoftwareUpdates
-- 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 an Amazon S3 presigned URL for an update file associated with a
-- specified @JobId@.
module Amazonka.Snowball.GetSoftwareUpdates
  ( -- * Creating a Request
    GetSoftwareUpdates (..),
    newGetSoftwareUpdates,

    -- * Request Lenses
    getSoftwareUpdates_jobId,

    -- * Destructuring the Response
    GetSoftwareUpdatesResponse (..),
    newGetSoftwareUpdatesResponse,

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

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

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

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

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

instance Data.ToHeaders GetSoftwareUpdates where
  toHeaders :: GetSoftwareUpdates -> 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.GetSoftwareUpdates" ::
                          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 GetSoftwareUpdates where
  toJSON :: GetSoftwareUpdates -> Value
toJSON GetSoftwareUpdates' {Text
jobId :: Text
$sel:jobId:GetSoftwareUpdates' :: GetSoftwareUpdates -> 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 GetSoftwareUpdates where
  toPath :: GetSoftwareUpdates -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetSoftwareUpdatesResponse' smart constructor.
data GetSoftwareUpdatesResponse = GetSoftwareUpdatesResponse'
  { -- | The Amazon S3 presigned URL for the update file associated with the
    -- specified @JobId@ value. The software update will be available for 2
    -- days after this request is made. To access an update after the 2 days
    -- have passed, you\'ll have to make another call to @GetSoftwareUpdates@.
    GetSoftwareUpdatesResponse -> Maybe Text
updatesURI :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetSoftwareUpdatesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSoftwareUpdatesResponse -> GetSoftwareUpdatesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSoftwareUpdatesResponse -> GetSoftwareUpdatesResponse -> Bool
$c/= :: GetSoftwareUpdatesResponse -> GetSoftwareUpdatesResponse -> Bool
== :: GetSoftwareUpdatesResponse -> GetSoftwareUpdatesResponse -> Bool
$c== :: GetSoftwareUpdatesResponse -> GetSoftwareUpdatesResponse -> Bool
Prelude.Eq, ReadPrec [GetSoftwareUpdatesResponse]
ReadPrec GetSoftwareUpdatesResponse
Int -> ReadS GetSoftwareUpdatesResponse
ReadS [GetSoftwareUpdatesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSoftwareUpdatesResponse]
$creadListPrec :: ReadPrec [GetSoftwareUpdatesResponse]
readPrec :: ReadPrec GetSoftwareUpdatesResponse
$creadPrec :: ReadPrec GetSoftwareUpdatesResponse
readList :: ReadS [GetSoftwareUpdatesResponse]
$creadList :: ReadS [GetSoftwareUpdatesResponse]
readsPrec :: Int -> ReadS GetSoftwareUpdatesResponse
$creadsPrec :: Int -> ReadS GetSoftwareUpdatesResponse
Prelude.Read, Int -> GetSoftwareUpdatesResponse -> ShowS
[GetSoftwareUpdatesResponse] -> ShowS
GetSoftwareUpdatesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSoftwareUpdatesResponse] -> ShowS
$cshowList :: [GetSoftwareUpdatesResponse] -> ShowS
show :: GetSoftwareUpdatesResponse -> String
$cshow :: GetSoftwareUpdatesResponse -> String
showsPrec :: Int -> GetSoftwareUpdatesResponse -> ShowS
$cshowsPrec :: Int -> GetSoftwareUpdatesResponse -> ShowS
Prelude.Show, forall x.
Rep GetSoftwareUpdatesResponse x -> GetSoftwareUpdatesResponse
forall x.
GetSoftwareUpdatesResponse -> Rep GetSoftwareUpdatesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSoftwareUpdatesResponse x -> GetSoftwareUpdatesResponse
$cfrom :: forall x.
GetSoftwareUpdatesResponse -> Rep GetSoftwareUpdatesResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSoftwareUpdatesResponse' 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:
--
-- 'updatesURI', 'getSoftwareUpdatesResponse_updatesURI' - The Amazon S3 presigned URL for the update file associated with the
-- specified @JobId@ value. The software update will be available for 2
-- days after this request is made. To access an update after the 2 days
-- have passed, you\'ll have to make another call to @GetSoftwareUpdates@.
--
-- 'httpStatus', 'getSoftwareUpdatesResponse_httpStatus' - The response's http status code.
newGetSoftwareUpdatesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSoftwareUpdatesResponse
newGetSoftwareUpdatesResponse :: Int -> GetSoftwareUpdatesResponse
newGetSoftwareUpdatesResponse Int
pHttpStatus_ =
  GetSoftwareUpdatesResponse'
    { $sel:updatesURI:GetSoftwareUpdatesResponse' :: Maybe Text
updatesURI =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSoftwareUpdatesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon S3 presigned URL for the update file associated with the
-- specified @JobId@ value. The software update will be available for 2
-- days after this request is made. To access an update after the 2 days
-- have passed, you\'ll have to make another call to @GetSoftwareUpdates@.
getSoftwareUpdatesResponse_updatesURI :: Lens.Lens' GetSoftwareUpdatesResponse (Prelude.Maybe Prelude.Text)
getSoftwareUpdatesResponse_updatesURI :: Lens' GetSoftwareUpdatesResponse (Maybe Text)
getSoftwareUpdatesResponse_updatesURI = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSoftwareUpdatesResponse' {Maybe Text
updatesURI :: Maybe Text
$sel:updatesURI:GetSoftwareUpdatesResponse' :: GetSoftwareUpdatesResponse -> Maybe Text
updatesURI} -> Maybe Text
updatesURI) (\s :: GetSoftwareUpdatesResponse
s@GetSoftwareUpdatesResponse' {} Maybe Text
a -> GetSoftwareUpdatesResponse
s {$sel:updatesURI:GetSoftwareUpdatesResponse' :: Maybe Text
updatesURI = Maybe Text
a} :: GetSoftwareUpdatesResponse)

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

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