{-# 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.AbortVaultLock
-- 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 aborts the vault locking process if the vault lock is not
-- in the @Locked@ state. If the vault lock is in the @Locked@ state when
-- this operation is requested, the operation returns an
-- @AccessDeniedException@ error. Aborting the vault locking process
-- removes the vault lock policy from the specified vault.
--
-- 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 get the state of a vault lock by
-- calling GetVaultLock. For more information about the vault locking
-- process, see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/vault-lock.html Amazon Glacier Vault Lock>.
-- For more information about vault lock policies, see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/vault-lock-policy.html Amazon Glacier Access Control with Vault Lock Policies>.
--
-- This operation is idempotent. You can successfully invoke this operation
-- multiple times, if the vault lock is in the @InProgress@ state or if
-- there is no policy associated with the vault.
module Amazonka.Glacier.AbortVaultLock
  ( -- * Creating a Request
    AbortVaultLock (..),
    newAbortVaultLock,

    -- * Request Lenses
    abortVaultLock_accountId,
    abortVaultLock_vaultName,

    -- * Destructuring the Response
    AbortVaultLockResponse (..),
    newAbortVaultLockResponse,
  )
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 @AbortVaultLock@.
--
-- /See:/ 'newAbortVaultLock' smart constructor.
data AbortVaultLock = AbortVaultLock'
  { -- | The @AccountId@ value is the AWS account ID. This value must match the
    -- AWS account ID associated with the credentials used to sign the request.
    -- You can either specify an AWS account ID or optionally a single \'@-@\'
    -- (hyphen), in which case Amazon Glacier uses the AWS account ID
    -- associated with the credentials used to sign the request. If you specify
    -- your account ID, do not include any hyphens (\'-\') in the ID.
    AbortVaultLock -> Text
accountId :: Prelude.Text,
    -- | The name of the vault.
    AbortVaultLock -> Text
vaultName :: Prelude.Text
  }
  deriving (AbortVaultLock -> AbortVaultLock -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AbortVaultLock -> AbortVaultLock -> Bool
$c/= :: AbortVaultLock -> AbortVaultLock -> Bool
== :: AbortVaultLock -> AbortVaultLock -> Bool
$c== :: AbortVaultLock -> AbortVaultLock -> Bool
Prelude.Eq, ReadPrec [AbortVaultLock]
ReadPrec AbortVaultLock
Int -> ReadS AbortVaultLock
ReadS [AbortVaultLock]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AbortVaultLock]
$creadListPrec :: ReadPrec [AbortVaultLock]
readPrec :: ReadPrec AbortVaultLock
$creadPrec :: ReadPrec AbortVaultLock
readList :: ReadS [AbortVaultLock]
$creadList :: ReadS [AbortVaultLock]
readsPrec :: Int -> ReadS AbortVaultLock
$creadsPrec :: Int -> ReadS AbortVaultLock
Prelude.Read, Int -> AbortVaultLock -> ShowS
[AbortVaultLock] -> ShowS
AbortVaultLock -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AbortVaultLock] -> ShowS
$cshowList :: [AbortVaultLock] -> ShowS
show :: AbortVaultLock -> String
$cshow :: AbortVaultLock -> String
showsPrec :: Int -> AbortVaultLock -> ShowS
$cshowsPrec :: Int -> AbortVaultLock -> ShowS
Prelude.Show, forall x. Rep AbortVaultLock x -> AbortVaultLock
forall x. AbortVaultLock -> Rep AbortVaultLock x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AbortVaultLock x -> AbortVaultLock
$cfrom :: forall x. AbortVaultLock -> Rep AbortVaultLock x
Prelude.Generic)

-- |
-- Create a value of 'AbortVaultLock' 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', 'abortVaultLock_accountId' - The @AccountId@ value is the AWS account ID. This value must match the
-- AWS account ID associated with the credentials used to sign the request.
-- You can either specify an AWS account ID or optionally a single \'@-@\'
-- (hyphen), in which case Amazon Glacier uses the AWS account ID
-- associated with the credentials used to sign the request. If you specify
-- your account ID, do not include any hyphens (\'-\') in the ID.
--
-- 'vaultName', 'abortVaultLock_vaultName' - The name of the vault.
newAbortVaultLock ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'vaultName'
  Prelude.Text ->
  AbortVaultLock
newAbortVaultLock :: Text -> Text -> AbortVaultLock
newAbortVaultLock Text
pAccountId_ Text
pVaultName_ =
  AbortVaultLock'
    { $sel:accountId:AbortVaultLock' :: Text
accountId = Text
pAccountId_,
      $sel:vaultName:AbortVaultLock' :: Text
vaultName = Text
pVaultName_
    }

-- | The @AccountId@ value is the AWS account ID. This value must match the
-- AWS account ID associated with the credentials used to sign the request.
-- You can either specify an AWS account ID or optionally a single \'@-@\'
-- (hyphen), in which case Amazon Glacier uses the AWS account ID
-- associated with the credentials used to sign the request. If you specify
-- your account ID, do not include any hyphens (\'-\') in the ID.
abortVaultLock_accountId :: Lens.Lens' AbortVaultLock Prelude.Text
abortVaultLock_accountId :: Lens' AbortVaultLock Text
abortVaultLock_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AbortVaultLock' {Text
accountId :: Text
$sel:accountId:AbortVaultLock' :: AbortVaultLock -> Text
accountId} -> Text
accountId) (\s :: AbortVaultLock
s@AbortVaultLock' {} Text
a -> AbortVaultLock
s {$sel:accountId:AbortVaultLock' :: Text
accountId = Text
a} :: AbortVaultLock)

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

instance Core.AWSRequest AbortVaultLock where
  type
    AWSResponse AbortVaultLock =
      AbortVaultLockResponse
  request :: (Service -> Service) -> AbortVaultLock -> Request AbortVaultLock
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.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy AbortVaultLock
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AbortVaultLock)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull AbortVaultLockResponse
AbortVaultLockResponse'

instance Prelude.Hashable AbortVaultLock where
  hashWithSalt :: Int -> AbortVaultLock -> Int
hashWithSalt Int
_salt AbortVaultLock' {Text
vaultName :: Text
accountId :: Text
$sel:vaultName:AbortVaultLock' :: AbortVaultLock -> Text
$sel:accountId:AbortVaultLock' :: AbortVaultLock -> 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 AbortVaultLock where
  rnf :: AbortVaultLock -> ()
rnf AbortVaultLock' {Text
vaultName :: Text
accountId :: Text
$sel:vaultName:AbortVaultLock' :: AbortVaultLock -> Text
$sel:accountId:AbortVaultLock' :: AbortVaultLock -> 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 AbortVaultLock where
  toHeaders :: AbortVaultLock -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath AbortVaultLock where
  toPath :: AbortVaultLock -> ByteString
toPath AbortVaultLock' {Text
vaultName :: Text
accountId :: Text
$sel:vaultName:AbortVaultLock' :: AbortVaultLock -> Text
$sel:accountId:AbortVaultLock' :: AbortVaultLock -> 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 AbortVaultLock where
  toQuery :: AbortVaultLock -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newAbortVaultLockResponse' smart constructor.
data AbortVaultLockResponse = AbortVaultLockResponse'
  {
  }
  deriving (AbortVaultLockResponse -> AbortVaultLockResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AbortVaultLockResponse -> AbortVaultLockResponse -> Bool
$c/= :: AbortVaultLockResponse -> AbortVaultLockResponse -> Bool
== :: AbortVaultLockResponse -> AbortVaultLockResponse -> Bool
$c== :: AbortVaultLockResponse -> AbortVaultLockResponse -> Bool
Prelude.Eq, ReadPrec [AbortVaultLockResponse]
ReadPrec AbortVaultLockResponse
Int -> ReadS AbortVaultLockResponse
ReadS [AbortVaultLockResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AbortVaultLockResponse]
$creadListPrec :: ReadPrec [AbortVaultLockResponse]
readPrec :: ReadPrec AbortVaultLockResponse
$creadPrec :: ReadPrec AbortVaultLockResponse
readList :: ReadS [AbortVaultLockResponse]
$creadList :: ReadS [AbortVaultLockResponse]
readsPrec :: Int -> ReadS AbortVaultLockResponse
$creadsPrec :: Int -> ReadS AbortVaultLockResponse
Prelude.Read, Int -> AbortVaultLockResponse -> ShowS
[AbortVaultLockResponse] -> ShowS
AbortVaultLockResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AbortVaultLockResponse] -> ShowS
$cshowList :: [AbortVaultLockResponse] -> ShowS
show :: AbortVaultLockResponse -> String
$cshow :: AbortVaultLockResponse -> String
showsPrec :: Int -> AbortVaultLockResponse -> ShowS
$cshowsPrec :: Int -> AbortVaultLockResponse -> ShowS
Prelude.Show, forall x. Rep AbortVaultLockResponse x -> AbortVaultLockResponse
forall x. AbortVaultLockResponse -> Rep AbortVaultLockResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AbortVaultLockResponse x -> AbortVaultLockResponse
$cfrom :: forall x. AbortVaultLockResponse -> Rep AbortVaultLockResponse x
Prelude.Generic)

-- |
-- Create a value of 'AbortVaultLockResponse' 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.
newAbortVaultLockResponse ::
  AbortVaultLockResponse
newAbortVaultLockResponse :: AbortVaultLockResponse
newAbortVaultLockResponse = AbortVaultLockResponse
AbortVaultLockResponse'

instance Prelude.NFData AbortVaultLockResponse where
  rnf :: AbortVaultLockResponse -> ()
rnf AbortVaultLockResponse
_ = ()