{-# 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.PurchaseProvisionedCapacity
-- 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 purchases a provisioned capacity unit for an AWS account.
module Amazonka.Glacier.PurchaseProvisionedCapacity
  ( -- * Creating a Request
    PurchaseProvisionedCapacity (..),
    newPurchaseProvisionedCapacity,

    -- * Request Lenses
    purchaseProvisionedCapacity_accountId,

    -- * Destructuring the Response
    PurchaseProvisionedCapacityResponse (..),
    newPurchaseProvisionedCapacityResponse,

    -- * Response Lenses
    purchaseProvisionedCapacityResponse_capacityId,
    purchaseProvisionedCapacityResponse_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

-- | /See:/ 'newPurchaseProvisionedCapacity' smart constructor.
data PurchaseProvisionedCapacity = PurchaseProvisionedCapacity'
  { -- | 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, don\'t
    -- include any hyphens (\'-\') in the ID.
    PurchaseProvisionedCapacity -> Text
accountId :: Prelude.Text
  }
  deriving (PurchaseProvisionedCapacity -> PurchaseProvisionedCapacity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PurchaseProvisionedCapacity -> PurchaseProvisionedCapacity -> Bool
$c/= :: PurchaseProvisionedCapacity -> PurchaseProvisionedCapacity -> Bool
== :: PurchaseProvisionedCapacity -> PurchaseProvisionedCapacity -> Bool
$c== :: PurchaseProvisionedCapacity -> PurchaseProvisionedCapacity -> Bool
Prelude.Eq, ReadPrec [PurchaseProvisionedCapacity]
ReadPrec PurchaseProvisionedCapacity
Int -> ReadS PurchaseProvisionedCapacity
ReadS [PurchaseProvisionedCapacity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PurchaseProvisionedCapacity]
$creadListPrec :: ReadPrec [PurchaseProvisionedCapacity]
readPrec :: ReadPrec PurchaseProvisionedCapacity
$creadPrec :: ReadPrec PurchaseProvisionedCapacity
readList :: ReadS [PurchaseProvisionedCapacity]
$creadList :: ReadS [PurchaseProvisionedCapacity]
readsPrec :: Int -> ReadS PurchaseProvisionedCapacity
$creadsPrec :: Int -> ReadS PurchaseProvisionedCapacity
Prelude.Read, Int -> PurchaseProvisionedCapacity -> ShowS
[PurchaseProvisionedCapacity] -> ShowS
PurchaseProvisionedCapacity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PurchaseProvisionedCapacity] -> ShowS
$cshowList :: [PurchaseProvisionedCapacity] -> ShowS
show :: PurchaseProvisionedCapacity -> String
$cshow :: PurchaseProvisionedCapacity -> String
showsPrec :: Int -> PurchaseProvisionedCapacity -> ShowS
$cshowsPrec :: Int -> PurchaseProvisionedCapacity -> ShowS
Prelude.Show, forall x.
Rep PurchaseProvisionedCapacity x -> PurchaseProvisionedCapacity
forall x.
PurchaseProvisionedCapacity -> Rep PurchaseProvisionedCapacity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PurchaseProvisionedCapacity x -> PurchaseProvisionedCapacity
$cfrom :: forall x.
PurchaseProvisionedCapacity -> Rep PurchaseProvisionedCapacity x
Prelude.Generic)

-- |
-- Create a value of 'PurchaseProvisionedCapacity' 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', 'purchaseProvisionedCapacity_accountId' - 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, don\'t
-- include any hyphens (\'-\') in the ID.
newPurchaseProvisionedCapacity ::
  -- | 'accountId'
  Prelude.Text ->
  PurchaseProvisionedCapacity
newPurchaseProvisionedCapacity :: Text -> PurchaseProvisionedCapacity
newPurchaseProvisionedCapacity Text
pAccountId_ =
  PurchaseProvisionedCapacity'
    { $sel:accountId:PurchaseProvisionedCapacity' :: Text
accountId =
        Text
pAccountId_
    }

-- | 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, don\'t
-- include any hyphens (\'-\') in the ID.
purchaseProvisionedCapacity_accountId :: Lens.Lens' PurchaseProvisionedCapacity Prelude.Text
purchaseProvisionedCapacity_accountId :: Lens' PurchaseProvisionedCapacity Text
purchaseProvisionedCapacity_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PurchaseProvisionedCapacity' {Text
accountId :: Text
$sel:accountId:PurchaseProvisionedCapacity' :: PurchaseProvisionedCapacity -> Text
accountId} -> Text
accountId) (\s :: PurchaseProvisionedCapacity
s@PurchaseProvisionedCapacity' {} Text
a -> PurchaseProvisionedCapacity
s {$sel:accountId:PurchaseProvisionedCapacity' :: Text
accountId = Text
a} :: PurchaseProvisionedCapacity)

instance Core.AWSRequest PurchaseProvisionedCapacity where
  type
    AWSResponse PurchaseProvisionedCapacity =
      PurchaseProvisionedCapacityResponse
  request :: (Service -> Service)
-> PurchaseProvisionedCapacity
-> Request PurchaseProvisionedCapacity
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, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy PurchaseProvisionedCapacity
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PurchaseProvisionedCapacity)))
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 -> Int -> PurchaseProvisionedCapacityResponse
PurchaseProvisionedCapacityResponse'
            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-capacity-id")
            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 PurchaseProvisionedCapacity where
  hashWithSalt :: Int -> PurchaseProvisionedCapacity -> Int
hashWithSalt Int
_salt PurchaseProvisionedCapacity' {Text
accountId :: Text
$sel:accountId:PurchaseProvisionedCapacity' :: PurchaseProvisionedCapacity -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountId

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

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

instance Data.ToJSON PurchaseProvisionedCapacity where
  toJSON :: PurchaseProvisionedCapacity -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath PurchaseProvisionedCapacity where
  toPath :: PurchaseProvisionedCapacity -> ByteString
toPath PurchaseProvisionedCapacity' {Text
accountId :: Text
$sel:accountId:PurchaseProvisionedCapacity' :: PurchaseProvisionedCapacity -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
accountId, ByteString
"/provisioned-capacity"]

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

-- | /See:/ 'newPurchaseProvisionedCapacityResponse' smart constructor.
data PurchaseProvisionedCapacityResponse = PurchaseProvisionedCapacityResponse'
  { -- | The ID that identifies the provisioned capacity unit.
    PurchaseProvisionedCapacityResponse -> Maybe Text
capacityId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    PurchaseProvisionedCapacityResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (PurchaseProvisionedCapacityResponse
-> PurchaseProvisionedCapacityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PurchaseProvisionedCapacityResponse
-> PurchaseProvisionedCapacityResponse -> Bool
$c/= :: PurchaseProvisionedCapacityResponse
-> PurchaseProvisionedCapacityResponse -> Bool
== :: PurchaseProvisionedCapacityResponse
-> PurchaseProvisionedCapacityResponse -> Bool
$c== :: PurchaseProvisionedCapacityResponse
-> PurchaseProvisionedCapacityResponse -> Bool
Prelude.Eq, ReadPrec [PurchaseProvisionedCapacityResponse]
ReadPrec PurchaseProvisionedCapacityResponse
Int -> ReadS PurchaseProvisionedCapacityResponse
ReadS [PurchaseProvisionedCapacityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PurchaseProvisionedCapacityResponse]
$creadListPrec :: ReadPrec [PurchaseProvisionedCapacityResponse]
readPrec :: ReadPrec PurchaseProvisionedCapacityResponse
$creadPrec :: ReadPrec PurchaseProvisionedCapacityResponse
readList :: ReadS [PurchaseProvisionedCapacityResponse]
$creadList :: ReadS [PurchaseProvisionedCapacityResponse]
readsPrec :: Int -> ReadS PurchaseProvisionedCapacityResponse
$creadsPrec :: Int -> ReadS PurchaseProvisionedCapacityResponse
Prelude.Read, Int -> PurchaseProvisionedCapacityResponse -> ShowS
[PurchaseProvisionedCapacityResponse] -> ShowS
PurchaseProvisionedCapacityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PurchaseProvisionedCapacityResponse] -> ShowS
$cshowList :: [PurchaseProvisionedCapacityResponse] -> ShowS
show :: PurchaseProvisionedCapacityResponse -> String
$cshow :: PurchaseProvisionedCapacityResponse -> String
showsPrec :: Int -> PurchaseProvisionedCapacityResponse -> ShowS
$cshowsPrec :: Int -> PurchaseProvisionedCapacityResponse -> ShowS
Prelude.Show, forall x.
Rep PurchaseProvisionedCapacityResponse x
-> PurchaseProvisionedCapacityResponse
forall x.
PurchaseProvisionedCapacityResponse
-> Rep PurchaseProvisionedCapacityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PurchaseProvisionedCapacityResponse x
-> PurchaseProvisionedCapacityResponse
$cfrom :: forall x.
PurchaseProvisionedCapacityResponse
-> Rep PurchaseProvisionedCapacityResponse x
Prelude.Generic)

-- |
-- Create a value of 'PurchaseProvisionedCapacityResponse' 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:
--
-- 'capacityId', 'purchaseProvisionedCapacityResponse_capacityId' - The ID that identifies the provisioned capacity unit.
--
-- 'httpStatus', 'purchaseProvisionedCapacityResponse_httpStatus' - The response's http status code.
newPurchaseProvisionedCapacityResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PurchaseProvisionedCapacityResponse
newPurchaseProvisionedCapacityResponse :: Int -> PurchaseProvisionedCapacityResponse
newPurchaseProvisionedCapacityResponse Int
pHttpStatus_ =
  PurchaseProvisionedCapacityResponse'
    { $sel:capacityId:PurchaseProvisionedCapacityResponse' :: Maybe Text
capacityId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PurchaseProvisionedCapacityResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID that identifies the provisioned capacity unit.
purchaseProvisionedCapacityResponse_capacityId :: Lens.Lens' PurchaseProvisionedCapacityResponse (Prelude.Maybe Prelude.Text)
purchaseProvisionedCapacityResponse_capacityId :: Lens' PurchaseProvisionedCapacityResponse (Maybe Text)
purchaseProvisionedCapacityResponse_capacityId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PurchaseProvisionedCapacityResponse' {Maybe Text
capacityId :: Maybe Text
$sel:capacityId:PurchaseProvisionedCapacityResponse' :: PurchaseProvisionedCapacityResponse -> Maybe Text
capacityId} -> Maybe Text
capacityId) (\s :: PurchaseProvisionedCapacityResponse
s@PurchaseProvisionedCapacityResponse' {} Maybe Text
a -> PurchaseProvisionedCapacityResponse
s {$sel:capacityId:PurchaseProvisionedCapacityResponse' :: Maybe Text
capacityId = Maybe Text
a} :: PurchaseProvisionedCapacityResponse)

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

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