{-# 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.UploadArchive
-- 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 adds an archive to a vault. This is a synchronous
-- operation, and for a successful upload, your data is durably persisted.
-- Amazon S3 Glacier returns the archive ID in the @x-amz-archive-id@
-- header of the response.
--
-- You must use the archive ID to access your data in Amazon S3 Glacier.
-- After you upload an archive, you should save the archive ID returned so
-- that you can retrieve or delete the archive later. Besides saving the
-- archive ID, you can also index it and give it a friendly name to allow
-- for better searching. You can also use the optional archive description
-- field to specify how the archive is referred to in an external index of
-- archives, such as you might create in Amazon DynamoDB. You can also get
-- the vault inventory to obtain a list of archive IDs in a vault. For more
-- information, see InitiateJob.
--
-- You must provide a SHA256 tree hash of the data you are uploading. For
-- information about computing a SHA256 tree hash, see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/checksum-calculations.html Computing Checksums>.
--
-- You can optionally specify an archive description of up to 1,024
-- printable ASCII characters. You can get the archive description when you
-- either retrieve the archive or get the vault inventory. For more
-- information, see InitiateJob. Amazon Glacier does not interpret the
-- description in any way. An archive description does not need to be
-- unique. You cannot use the description to retrieve or sort the archive
-- list.
--
-- Archives are immutable. After you upload an archive, you cannot edit the
-- archive or its description.
--
-- 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 conceptual information and underlying REST API, see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/uploading-an-archive.html Uploading an Archive in Amazon Glacier>
-- and
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/api-archive-post.html Upload Archive>
-- in the /Amazon Glacier Developer Guide/.
module Amazonka.Glacier.UploadArchive
  ( -- * Creating a Request
    UploadArchive (..),
    newUploadArchive,

    -- * Request Lenses
    uploadArchive_archiveDescription,
    uploadArchive_checksum,
    uploadArchive_vaultName,
    uploadArchive_accountId,
    uploadArchive_body,

    -- * Destructuring the Response
    ArchiveCreationOutput (..),
    newArchiveCreationOutput,

    -- * Response Lenses
    archiveCreationOutput_archiveId,
    archiveCreationOutput_checksum,
    archiveCreationOutput_location,
  )
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 to add an archive to a vault.
--
-- /See:/ 'newUploadArchive' smart constructor.
data UploadArchive = UploadArchive'
  { -- | The optional description of the archive you are uploading.
    UploadArchive -> Maybe Text
archiveDescription :: Prelude.Maybe Prelude.Text,
    -- | The SHA256 tree hash of the data being uploaded.
    UploadArchive -> Maybe Text
checksum :: Prelude.Maybe Prelude.Text,
    -- | The name of the vault.
    UploadArchive -> Text
vaultName :: Prelude.Text,
    -- | 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.
    UploadArchive -> Text
accountId :: Prelude.Text,
    -- | The data to upload.
    UploadArchive -> HashedBody
body :: Data.HashedBody
  }
  deriving (Int -> UploadArchive -> ShowS
[UploadArchive] -> ShowS
UploadArchive -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadArchive] -> ShowS
$cshowList :: [UploadArchive] -> ShowS
show :: UploadArchive -> String
$cshow :: UploadArchive -> String
showsPrec :: Int -> UploadArchive -> ShowS
$cshowsPrec :: Int -> UploadArchive -> ShowS
Prelude.Show, forall x. Rep UploadArchive x -> UploadArchive
forall x. UploadArchive -> Rep UploadArchive x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UploadArchive x -> UploadArchive
$cfrom :: forall x. UploadArchive -> Rep UploadArchive x
Prelude.Generic)

-- |
-- Create a value of 'UploadArchive' 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:
--
-- 'archiveDescription', 'uploadArchive_archiveDescription' - The optional description of the archive you are uploading.
--
-- 'checksum', 'uploadArchive_checksum' - The SHA256 tree hash of the data being uploaded.
--
-- 'vaultName', 'uploadArchive_vaultName' - The name of the vault.
--
-- 'accountId', 'uploadArchive_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.
--
-- 'body', 'uploadArchive_body' - The data to upload.
newUploadArchive ::
  -- | 'vaultName'
  Prelude.Text ->
  -- | 'accountId'
  Prelude.Text ->
  -- | 'body'
  Data.HashedBody ->
  UploadArchive
newUploadArchive :: Text -> Text -> HashedBody -> UploadArchive
newUploadArchive Text
pVaultName_ Text
pAccountId_ HashedBody
pBody_ =
  UploadArchive'
    { $sel:archiveDescription:UploadArchive' :: Maybe Text
archiveDescription =
        forall a. Maybe a
Prelude.Nothing,
      $sel:checksum:UploadArchive' :: Maybe Text
checksum = forall a. Maybe a
Prelude.Nothing,
      $sel:vaultName:UploadArchive' :: Text
vaultName = Text
pVaultName_,
      $sel:accountId:UploadArchive' :: Text
accountId = Text
pAccountId_,
      $sel:body:UploadArchive' :: HashedBody
body = HashedBody
pBody_
    }

-- | The optional description of the archive you are uploading.
uploadArchive_archiveDescription :: Lens.Lens' UploadArchive (Prelude.Maybe Prelude.Text)
uploadArchive_archiveDescription :: Lens' UploadArchive (Maybe Text)
uploadArchive_archiveDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadArchive' {Maybe Text
archiveDescription :: Maybe Text
$sel:archiveDescription:UploadArchive' :: UploadArchive -> Maybe Text
archiveDescription} -> Maybe Text
archiveDescription) (\s :: UploadArchive
s@UploadArchive' {} Maybe Text
a -> UploadArchive
s {$sel:archiveDescription:UploadArchive' :: Maybe Text
archiveDescription = Maybe Text
a} :: UploadArchive)

-- | The SHA256 tree hash of the data being uploaded.
uploadArchive_checksum :: Lens.Lens' UploadArchive (Prelude.Maybe Prelude.Text)
uploadArchive_checksum :: Lens' UploadArchive (Maybe Text)
uploadArchive_checksum = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadArchive' {Maybe Text
checksum :: Maybe Text
$sel:checksum:UploadArchive' :: UploadArchive -> Maybe Text
checksum} -> Maybe Text
checksum) (\s :: UploadArchive
s@UploadArchive' {} Maybe Text
a -> UploadArchive
s {$sel:checksum:UploadArchive' :: Maybe Text
checksum = Maybe Text
a} :: UploadArchive)

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

-- | 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.
uploadArchive_accountId :: Lens.Lens' UploadArchive Prelude.Text
uploadArchive_accountId :: Lens' UploadArchive Text
uploadArchive_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadArchive' {Text
accountId :: Text
$sel:accountId:UploadArchive' :: UploadArchive -> Text
accountId} -> Text
accountId) (\s :: UploadArchive
s@UploadArchive' {} Text
a -> UploadArchive
s {$sel:accountId:UploadArchive' :: Text
accountId = Text
a} :: UploadArchive)

-- | The data to upload.
uploadArchive_body :: Lens.Lens' UploadArchive Data.HashedBody
uploadArchive_body :: Lens' UploadArchive HashedBody
uploadArchive_body = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadArchive' {HashedBody
body :: HashedBody
$sel:body:UploadArchive' :: UploadArchive -> HashedBody
body} -> HashedBody
body) (\s :: UploadArchive
s@UploadArchive' {} HashedBody
a -> UploadArchive
s {$sel:body:UploadArchive' :: HashedBody
body = HashedBody
a} :: UploadArchive)

instance Core.AWSRequest UploadArchive where
  type
    AWSResponse UploadArchive =
      ArchiveCreationOutput
  request :: (Service -> Service) -> UploadArchive -> Request UploadArchive
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, ToBody a) => Service -> a -> Request a
Request.postBody (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UploadArchive
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UploadArchive)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Maybe Text -> Maybe Text -> Maybe Text -> ArchiveCreationOutput
ArchiveCreationOutput'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-archive-id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-sha256-tree-hash")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Location")
      )

instance Data.ToBody UploadArchive where
  toBody :: UploadArchive -> RequestBody
toBody UploadArchive' {Maybe Text
Text
HashedBody
body :: HashedBody
accountId :: Text
vaultName :: Text
checksum :: Maybe Text
archiveDescription :: Maybe Text
$sel:body:UploadArchive' :: UploadArchive -> HashedBody
$sel:accountId:UploadArchive' :: UploadArchive -> Text
$sel:vaultName:UploadArchive' :: UploadArchive -> Text
$sel:checksum:UploadArchive' :: UploadArchive -> Maybe Text
$sel:archiveDescription:UploadArchive' :: UploadArchive -> Maybe Text
..} = forall a. ToBody a => a -> RequestBody
Data.toBody HashedBody
body

instance Data.ToHeaders UploadArchive where
  toHeaders :: UploadArchive -> ResponseHeaders
toHeaders UploadArchive' {Maybe Text
Text
HashedBody
body :: HashedBody
accountId :: Text
vaultName :: Text
checksum :: Maybe Text
archiveDescription :: Maybe Text
$sel:body:UploadArchive' :: UploadArchive -> HashedBody
$sel:accountId:UploadArchive' :: UploadArchive -> Text
$sel:vaultName:UploadArchive' :: UploadArchive -> Text
$sel:checksum:UploadArchive' :: UploadArchive -> Maybe Text
$sel:archiveDescription:UploadArchive' :: UploadArchive -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"x-amz-archive-description"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
archiveDescription,
        HeaderName
"x-amz-sha256-tree-hash" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
checksum
      ]

instance Data.ToPath UploadArchive where
  toPath :: UploadArchive -> ByteString
toPath UploadArchive' {Maybe Text
Text
HashedBody
body :: HashedBody
accountId :: Text
vaultName :: Text
checksum :: Maybe Text
archiveDescription :: Maybe Text
$sel:body:UploadArchive' :: UploadArchive -> HashedBody
$sel:accountId:UploadArchive' :: UploadArchive -> Text
$sel:vaultName:UploadArchive' :: UploadArchive -> Text
$sel:checksum:UploadArchive' :: UploadArchive -> Maybe Text
$sel:archiveDescription:UploadArchive' :: UploadArchive -> Maybe 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
"/archives"
      ]

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