{-# 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.GetVaultLock
-- 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 retrieves the following attributes from the @lock-policy@
-- subresource set on the specified vault:
--
-- -   The vault lock policy set on the vault.
--
-- -   The state of the vault lock, which is either @InProgess@ or
--     @Locked@.
--
-- -   When the lock ID expires. The lock ID is used to complete the vault
--     locking process.
--
-- -   When the vault lock was initiated and put into the @InProgress@
--     state.
--
-- A vault lock is put into the @InProgress@ state by calling
-- InitiateVaultLock. A vault lock is put into the @Locked@ state by
-- calling CompleteVaultLock. You can abort the vault locking process by
-- calling AbortVaultLock. For more information about the vault locking
-- process,
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/vault-lock.html Amazon Glacier Vault Lock>.
--
-- If there is no vault lock policy set on the vault, the operation returns
-- a @404 Not found@ error. For more information about vault lock policies,
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/vault-lock-policy.html Amazon Glacier Access Control with Vault Lock Policies>.
module Amazonka.Glacier.GetVaultLock
  ( -- * Creating a Request
    GetVaultLock (..),
    newGetVaultLock,

    -- * Request Lenses
    getVaultLock_accountId,
    getVaultLock_vaultName,

    -- * Destructuring the Response
    GetVaultLockResponse (..),
    newGetVaultLockResponse,

    -- * Response Lenses
    getVaultLockResponse_creationDate,
    getVaultLockResponse_expirationDate,
    getVaultLockResponse_policy,
    getVaultLockResponse_state,
    getVaultLockResponse_httpStatus,
  )
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

-- | The input values for @GetVaultLock@.
--
-- /See:/ 'newGetVaultLock' smart constructor.
data GetVaultLock = GetVaultLock'
  { -- | 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.
    GetVaultLock -> Text
accountId :: Prelude.Text,
    -- | The name of the vault.
    GetVaultLock -> Text
vaultName :: Prelude.Text
  }
  deriving (GetVaultLock -> GetVaultLock -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetVaultLock -> GetVaultLock -> Bool
$c/= :: GetVaultLock -> GetVaultLock -> Bool
== :: GetVaultLock -> GetVaultLock -> Bool
$c== :: GetVaultLock -> GetVaultLock -> Bool
Prelude.Eq, ReadPrec [GetVaultLock]
ReadPrec GetVaultLock
Int -> ReadS GetVaultLock
ReadS [GetVaultLock]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetVaultLock]
$creadListPrec :: ReadPrec [GetVaultLock]
readPrec :: ReadPrec GetVaultLock
$creadPrec :: ReadPrec GetVaultLock
readList :: ReadS [GetVaultLock]
$creadList :: ReadS [GetVaultLock]
readsPrec :: Int -> ReadS GetVaultLock
$creadsPrec :: Int -> ReadS GetVaultLock
Prelude.Read, Int -> GetVaultLock -> ShowS
[GetVaultLock] -> ShowS
GetVaultLock -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetVaultLock] -> ShowS
$cshowList :: [GetVaultLock] -> ShowS
show :: GetVaultLock -> String
$cshow :: GetVaultLock -> String
showsPrec :: Int -> GetVaultLock -> ShowS
$cshowsPrec :: Int -> GetVaultLock -> ShowS
Prelude.Show, forall x. Rep GetVaultLock x -> GetVaultLock
forall x. GetVaultLock -> Rep GetVaultLock x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetVaultLock x -> GetVaultLock
$cfrom :: forall x. GetVaultLock -> Rep GetVaultLock x
Prelude.Generic)

-- |
-- Create a value of 'GetVaultLock' 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', 'getVaultLock_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', 'getVaultLock_vaultName' - The name of the vault.
newGetVaultLock ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'vaultName'
  Prelude.Text ->
  GetVaultLock
newGetVaultLock :: Text -> Text -> GetVaultLock
newGetVaultLock Text
pAccountId_ Text
pVaultName_ =
  GetVaultLock'
    { $sel:accountId:GetVaultLock' :: Text
accountId = Text
pAccountId_,
      $sel:vaultName:GetVaultLock' :: 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.
getVaultLock_accountId :: Lens.Lens' GetVaultLock Prelude.Text
getVaultLock_accountId :: Lens' GetVaultLock Text
getVaultLock_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetVaultLock' {Text
accountId :: Text
$sel:accountId:GetVaultLock' :: GetVaultLock -> Text
accountId} -> Text
accountId) (\s :: GetVaultLock
s@GetVaultLock' {} Text
a -> GetVaultLock
s {$sel:accountId:GetVaultLock' :: Text
accountId = Text
a} :: GetVaultLock)

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

instance Core.AWSRequest GetVaultLock where
  type AWSResponse GetVaultLock = GetVaultLockResponse
  request :: (Service -> Service) -> GetVaultLock -> Request GetVaultLock
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 GetVaultLock
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetVaultLock)))
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
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> GetVaultLockResponse
GetVaultLockResponse'
            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
"CreationDate")
            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
"ExpirationDate")
            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
"Policy")
            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
"State")
            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 GetVaultLock where
  hashWithSalt :: Int -> GetVaultLock -> Int
hashWithSalt Int
_salt GetVaultLock' {Text
vaultName :: Text
accountId :: Text
$sel:vaultName:GetVaultLock' :: GetVaultLock -> Text
$sel:accountId:GetVaultLock' :: GetVaultLock -> 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 GetVaultLock where
  rnf :: GetVaultLock -> ()
rnf GetVaultLock' {Text
vaultName :: Text
accountId :: Text
$sel:vaultName:GetVaultLock' :: GetVaultLock -> Text
$sel:accountId:GetVaultLock' :: GetVaultLock -> 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 GetVaultLock where
  toHeaders :: GetVaultLock -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

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

-- | Contains the Amazon S3 Glacier response to your request.
--
-- /See:/ 'newGetVaultLockResponse' smart constructor.
data GetVaultLockResponse = GetVaultLockResponse'
  { -- | The UTC date and time at which the vault lock was put into the
    -- @InProgress@ state.
    GetVaultLockResponse -> Maybe Text
creationDate :: Prelude.Maybe Prelude.Text,
    -- | The UTC date and time at which the lock ID expires. This value can be
    -- @null@ if the vault lock is in a @Locked@ state.
    GetVaultLockResponse -> Maybe Text
expirationDate :: Prelude.Maybe Prelude.Text,
    -- | The vault lock policy as a JSON string, which uses \"\\\" as an escape
    -- character.
    GetVaultLockResponse -> Maybe Text
policy :: Prelude.Maybe Prelude.Text,
    -- | The state of the vault lock. @InProgress@ or @Locked@.
    GetVaultLockResponse -> Maybe Text
state :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetVaultLockResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetVaultLockResponse -> GetVaultLockResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetVaultLockResponse -> GetVaultLockResponse -> Bool
$c/= :: GetVaultLockResponse -> GetVaultLockResponse -> Bool
== :: GetVaultLockResponse -> GetVaultLockResponse -> Bool
$c== :: GetVaultLockResponse -> GetVaultLockResponse -> Bool
Prelude.Eq, ReadPrec [GetVaultLockResponse]
ReadPrec GetVaultLockResponse
Int -> ReadS GetVaultLockResponse
ReadS [GetVaultLockResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetVaultLockResponse]
$creadListPrec :: ReadPrec [GetVaultLockResponse]
readPrec :: ReadPrec GetVaultLockResponse
$creadPrec :: ReadPrec GetVaultLockResponse
readList :: ReadS [GetVaultLockResponse]
$creadList :: ReadS [GetVaultLockResponse]
readsPrec :: Int -> ReadS GetVaultLockResponse
$creadsPrec :: Int -> ReadS GetVaultLockResponse
Prelude.Read, Int -> GetVaultLockResponse -> ShowS
[GetVaultLockResponse] -> ShowS
GetVaultLockResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetVaultLockResponse] -> ShowS
$cshowList :: [GetVaultLockResponse] -> ShowS
show :: GetVaultLockResponse -> String
$cshow :: GetVaultLockResponse -> String
showsPrec :: Int -> GetVaultLockResponse -> ShowS
$cshowsPrec :: Int -> GetVaultLockResponse -> ShowS
Prelude.Show, forall x. Rep GetVaultLockResponse x -> GetVaultLockResponse
forall x. GetVaultLockResponse -> Rep GetVaultLockResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetVaultLockResponse x -> GetVaultLockResponse
$cfrom :: forall x. GetVaultLockResponse -> Rep GetVaultLockResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetVaultLockResponse' 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:
--
-- 'creationDate', 'getVaultLockResponse_creationDate' - The UTC date and time at which the vault lock was put into the
-- @InProgress@ state.
--
-- 'expirationDate', 'getVaultLockResponse_expirationDate' - The UTC date and time at which the lock ID expires. This value can be
-- @null@ if the vault lock is in a @Locked@ state.
--
-- 'policy', 'getVaultLockResponse_policy' - The vault lock policy as a JSON string, which uses \"\\\" as an escape
-- character.
--
-- 'state', 'getVaultLockResponse_state' - The state of the vault lock. @InProgress@ or @Locked@.
--
-- 'httpStatus', 'getVaultLockResponse_httpStatus' - The response's http status code.
newGetVaultLockResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetVaultLockResponse
newGetVaultLockResponse :: Int -> GetVaultLockResponse
newGetVaultLockResponse Int
pHttpStatus_ =
  GetVaultLockResponse'
    { $sel:creationDate:GetVaultLockResponse' :: Maybe Text
creationDate =
        forall a. Maybe a
Prelude.Nothing,
      $sel:expirationDate:GetVaultLockResponse' :: Maybe Text
expirationDate = forall a. Maybe a
Prelude.Nothing,
      $sel:policy:GetVaultLockResponse' :: Maybe Text
policy = forall a. Maybe a
Prelude.Nothing,
      $sel:state:GetVaultLockResponse' :: Maybe Text
state = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetVaultLockResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The UTC date and time at which the vault lock was put into the
-- @InProgress@ state.
getVaultLockResponse_creationDate :: Lens.Lens' GetVaultLockResponse (Prelude.Maybe Prelude.Text)
getVaultLockResponse_creationDate :: Lens' GetVaultLockResponse (Maybe Text)
getVaultLockResponse_creationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetVaultLockResponse' {Maybe Text
creationDate :: Maybe Text
$sel:creationDate:GetVaultLockResponse' :: GetVaultLockResponse -> Maybe Text
creationDate} -> Maybe Text
creationDate) (\s :: GetVaultLockResponse
s@GetVaultLockResponse' {} Maybe Text
a -> GetVaultLockResponse
s {$sel:creationDate:GetVaultLockResponse' :: Maybe Text
creationDate = Maybe Text
a} :: GetVaultLockResponse)

-- | The UTC date and time at which the lock ID expires. This value can be
-- @null@ if the vault lock is in a @Locked@ state.
getVaultLockResponse_expirationDate :: Lens.Lens' GetVaultLockResponse (Prelude.Maybe Prelude.Text)
getVaultLockResponse_expirationDate :: Lens' GetVaultLockResponse (Maybe Text)
getVaultLockResponse_expirationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetVaultLockResponse' {Maybe Text
expirationDate :: Maybe Text
$sel:expirationDate:GetVaultLockResponse' :: GetVaultLockResponse -> Maybe Text
expirationDate} -> Maybe Text
expirationDate) (\s :: GetVaultLockResponse
s@GetVaultLockResponse' {} Maybe Text
a -> GetVaultLockResponse
s {$sel:expirationDate:GetVaultLockResponse' :: Maybe Text
expirationDate = Maybe Text
a} :: GetVaultLockResponse)

-- | The vault lock policy as a JSON string, which uses \"\\\" as an escape
-- character.
getVaultLockResponse_policy :: Lens.Lens' GetVaultLockResponse (Prelude.Maybe Prelude.Text)
getVaultLockResponse_policy :: Lens' GetVaultLockResponse (Maybe Text)
getVaultLockResponse_policy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetVaultLockResponse' {Maybe Text
policy :: Maybe Text
$sel:policy:GetVaultLockResponse' :: GetVaultLockResponse -> Maybe Text
policy} -> Maybe Text
policy) (\s :: GetVaultLockResponse
s@GetVaultLockResponse' {} Maybe Text
a -> GetVaultLockResponse
s {$sel:policy:GetVaultLockResponse' :: Maybe Text
policy = Maybe Text
a} :: GetVaultLockResponse)

-- | The state of the vault lock. @InProgress@ or @Locked@.
getVaultLockResponse_state :: Lens.Lens' GetVaultLockResponse (Prelude.Maybe Prelude.Text)
getVaultLockResponse_state :: Lens' GetVaultLockResponse (Maybe Text)
getVaultLockResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetVaultLockResponse' {Maybe Text
state :: Maybe Text
$sel:state:GetVaultLockResponse' :: GetVaultLockResponse -> Maybe Text
state} -> Maybe Text
state) (\s :: GetVaultLockResponse
s@GetVaultLockResponse' {} Maybe Text
a -> GetVaultLockResponse
s {$sel:state:GetVaultLockResponse' :: Maybe Text
state = Maybe Text
a} :: GetVaultLockResponse)

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

instance Prelude.NFData GetVaultLockResponse where
  rnf :: GetVaultLockResponse -> ()
rnf GetVaultLockResponse' {Int
Maybe Text
httpStatus :: Int
state :: Maybe Text
policy :: Maybe Text
expirationDate :: Maybe Text
creationDate :: Maybe Text
$sel:httpStatus:GetVaultLockResponse' :: GetVaultLockResponse -> Int
$sel:state:GetVaultLockResponse' :: GetVaultLockResponse -> Maybe Text
$sel:policy:GetVaultLockResponse' :: GetVaultLockResponse -> Maybe Text
$sel:expirationDate:GetVaultLockResponse' :: GetVaultLockResponse -> Maybe Text
$sel:creationDate:GetVaultLockResponse' :: GetVaultLockResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
creationDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
expirationDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus