{-# 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.DescribeVault
-- 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 vault, including the vault\'s
-- Amazon Resource Name (ARN), the date the vault was created, the number
-- of archives it contains, and the total size of all the archives in the
-- vault. The number of archives and their total size are as of the last
-- inventory generation. This means that if you add or remove an archive
-- from a vault, and then immediately use Describe Vault, the change in
-- contents will not be immediately reflected. If you want to retrieve the
-- latest inventory of the vault, use InitiateJob. Amazon S3 Glacier
-- generates vault inventories approximately daily. For more information,
-- see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/vault-inventory.html Downloading a Vault Inventory in Amazon S3 Glacier>.
--
-- 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/retrieving-vault-info.html Retrieving Vault Metadata in Amazon S3 Glacier>
-- and
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/api-vault-get.html Describe Vault>
-- in the /Amazon Glacier Developer Guide/.
module Amazonka.Glacier.DescribeVault
  ( -- * Creating a Request
    DescribeVault (..),
    newDescribeVault,

    -- * Request Lenses
    describeVault_accountId,
    describeVault_vaultName,

    -- * Destructuring the Response
    DescribeVaultOutput (..),
    newDescribeVaultOutput,

    -- * Response Lenses
    describeVaultOutput_creationDate,
    describeVaultOutput_lastInventoryDate,
    describeVaultOutput_numberOfArchives,
    describeVaultOutput_sizeInBytes,
    describeVaultOutput_vaultARN,
    describeVaultOutput_vaultName,
  )
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 metadata for a specific vault in Amazon
-- Glacier.
--
-- /See:/ 'newDescribeVault' smart constructor.
data DescribeVault = DescribeVault'
  { -- | 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.
    DescribeVault -> Text
accountId :: Prelude.Text,
    -- | The name of the vault.
    DescribeVault -> Text
vaultName :: Prelude.Text
  }
  deriving (DescribeVault -> DescribeVault -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeVault -> DescribeVault -> Bool
$c/= :: DescribeVault -> DescribeVault -> Bool
== :: DescribeVault -> DescribeVault -> Bool
$c== :: DescribeVault -> DescribeVault -> Bool
Prelude.Eq, ReadPrec [DescribeVault]
ReadPrec DescribeVault
Int -> ReadS DescribeVault
ReadS [DescribeVault]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeVault]
$creadListPrec :: ReadPrec [DescribeVault]
readPrec :: ReadPrec DescribeVault
$creadPrec :: ReadPrec DescribeVault
readList :: ReadS [DescribeVault]
$creadList :: ReadS [DescribeVault]
readsPrec :: Int -> ReadS DescribeVault
$creadsPrec :: Int -> ReadS DescribeVault
Prelude.Read, Int -> DescribeVault -> ShowS
[DescribeVault] -> ShowS
DescribeVault -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeVault] -> ShowS
$cshowList :: [DescribeVault] -> ShowS
show :: DescribeVault -> String
$cshow :: DescribeVault -> String
showsPrec :: Int -> DescribeVault -> ShowS
$cshowsPrec :: Int -> DescribeVault -> ShowS
Prelude.Show, forall x. Rep DescribeVault x -> DescribeVault
forall x. DescribeVault -> Rep DescribeVault x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeVault x -> DescribeVault
$cfrom :: forall x. DescribeVault -> Rep DescribeVault x
Prelude.Generic)

-- |
-- Create a value of 'DescribeVault' 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', 'describeVault_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', 'describeVault_vaultName' - The name of the vault.
newDescribeVault ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'vaultName'
  Prelude.Text ->
  DescribeVault
newDescribeVault :: Text -> Text -> DescribeVault
newDescribeVault Text
pAccountId_ Text
pVaultName_ =
  DescribeVault'
    { $sel:accountId:DescribeVault' :: Text
accountId = Text
pAccountId_,
      $sel:vaultName:DescribeVault' :: Text
vaultName = Text
pVaultName_
    }

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

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

instance Core.AWSRequest DescribeVault where
  type AWSResponse DescribeVault = DescribeVaultOutput
  request :: (Service -> Service) -> DescribeVault -> Request DescribeVault
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 DescribeVault
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeVault)))
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 DescribeVault where
  hashWithSalt :: Int -> DescribeVault -> Int
hashWithSalt Int
_salt DescribeVault' {Text
vaultName :: Text
accountId :: Text
$sel:vaultName:DescribeVault' :: DescribeVault -> Text
$sel:accountId:DescribeVault' :: DescribeVault -> 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

instance Prelude.NFData DescribeVault where
  rnf :: DescribeVault -> ()
rnf DescribeVault' {Text
vaultName :: Text
accountId :: Text
$sel:vaultName:DescribeVault' :: DescribeVault -> Text
$sel:accountId:DescribeVault' :: DescribeVault -> 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

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

instance Data.ToPath DescribeVault where
  toPath :: DescribeVault -> ByteString
toPath DescribeVault' {Text
vaultName :: Text
accountId :: Text
$sel:vaultName:DescribeVault' :: DescribeVault -> Text
$sel:accountId:DescribeVault' :: DescribeVault -> 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
      ]

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