{-# 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.StorageGateway.CreateTapeWithBarcode
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a virtual tape by using your own barcode. You write data to the
-- virtual tape and then archive the tape. A barcode is unique and cannot
-- be reused if it has already been used on a tape. This applies to
-- barcodes used on deleted tapes. This operation is only supported in the
-- tape gateway type.
--
-- Cache storage must be allocated to the gateway before you can create a
-- virtual tape. Use the AddCache operation to add cache storage to a
-- gateway.
module Amazonka.StorageGateway.CreateTapeWithBarcode
  ( -- * Creating a Request
    CreateTapeWithBarcode (..),
    newCreateTapeWithBarcode,

    -- * Request Lenses
    createTapeWithBarcode_kmsEncrypted,
    createTapeWithBarcode_kmsKey,
    createTapeWithBarcode_poolId,
    createTapeWithBarcode_tags,
    createTapeWithBarcode_worm,
    createTapeWithBarcode_gatewayARN,
    createTapeWithBarcode_tapeSizeInBytes,
    createTapeWithBarcode_tapeBarcode,

    -- * Destructuring the Response
    CreateTapeWithBarcodeResponse (..),
    newCreateTapeWithBarcodeResponse,

    -- * Response Lenses
    createTapeWithBarcodeResponse_tapeARN,
    createTapeWithBarcodeResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.StorageGateway.Types

-- | CreateTapeWithBarcodeInput
--
-- /See:/ 'newCreateTapeWithBarcode' smart constructor.
data CreateTapeWithBarcode = CreateTapeWithBarcode'
  { -- | Set to @true@ to use Amazon S3 server-side encryption with your own KMS
    -- key, or @false@ to use a key managed by Amazon S3. Optional.
    --
    -- Valid Values: @true@ | @false@
    CreateTapeWithBarcode -> Maybe Bool
kmsEncrypted :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) of a symmetric customer master key (CMK)
    -- used for Amazon S3 server-side encryption. Storage Gateway does not
    -- support asymmetric CMKs. This value can only be set when @KMSEncrypted@
    -- is @true@. Optional.
    CreateTapeWithBarcode -> Maybe Text
kmsKey :: Prelude.Maybe Prelude.Text,
    -- | The ID of the pool that you want to add your tape to for archiving. The
    -- tape in this pool is archived in the S3 storage class that is associated
    -- with the pool. When you use your backup application to eject the tape,
    -- the tape is archived directly into the storage class (S3 Glacier or S3
    -- Deep Archive) that corresponds to the pool.
    CreateTapeWithBarcode -> Maybe Text
poolId :: Prelude.Maybe Prelude.Text,
    -- | A list of up to 50 tags that can be assigned to a virtual tape that has
    -- a barcode. Each tag is a key-value pair.
    --
    -- Valid characters for key and value are letters, spaces, and numbers
    -- representable in UTF-8 format, and the following special characters: + -
    -- = . _ : \/ \@. The maximum length of a tag\'s key is 128 characters, and
    -- the maximum length for a tag\'s value is 256.
    CreateTapeWithBarcode -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | Set to @TRUE@ if the tape you are creating is to be configured as a
    -- write-once-read-many (WORM) tape.
    CreateTapeWithBarcode -> Maybe Bool
worm :: Prelude.Maybe Prelude.Bool,
    -- | The unique Amazon Resource Name (ARN) that represents the gateway to
    -- associate the virtual tape with. Use the ListGateways operation to
    -- return a list of gateways for your account and Amazon Web Services
    -- Region.
    CreateTapeWithBarcode -> Text
gatewayARN :: Prelude.Text,
    -- | The size, in bytes, of the virtual tape that you want to create.
    --
    -- The size must be aligned by gigabyte (1024*1024*1024 bytes).
    CreateTapeWithBarcode -> Integer
tapeSizeInBytes :: Prelude.Integer,
    -- | The barcode that you want to assign to the tape.
    --
    -- Barcodes cannot be reused. This includes barcodes used for tapes that
    -- have been deleted.
    CreateTapeWithBarcode -> Text
tapeBarcode :: Prelude.Text
  }
  deriving (CreateTapeWithBarcode -> CreateTapeWithBarcode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateTapeWithBarcode -> CreateTapeWithBarcode -> Bool
$c/= :: CreateTapeWithBarcode -> CreateTapeWithBarcode -> Bool
== :: CreateTapeWithBarcode -> CreateTapeWithBarcode -> Bool
$c== :: CreateTapeWithBarcode -> CreateTapeWithBarcode -> Bool
Prelude.Eq, ReadPrec [CreateTapeWithBarcode]
ReadPrec CreateTapeWithBarcode
Int -> ReadS CreateTapeWithBarcode
ReadS [CreateTapeWithBarcode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateTapeWithBarcode]
$creadListPrec :: ReadPrec [CreateTapeWithBarcode]
readPrec :: ReadPrec CreateTapeWithBarcode
$creadPrec :: ReadPrec CreateTapeWithBarcode
readList :: ReadS [CreateTapeWithBarcode]
$creadList :: ReadS [CreateTapeWithBarcode]
readsPrec :: Int -> ReadS CreateTapeWithBarcode
$creadsPrec :: Int -> ReadS CreateTapeWithBarcode
Prelude.Read, Int -> CreateTapeWithBarcode -> ShowS
[CreateTapeWithBarcode] -> ShowS
CreateTapeWithBarcode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateTapeWithBarcode] -> ShowS
$cshowList :: [CreateTapeWithBarcode] -> ShowS
show :: CreateTapeWithBarcode -> String
$cshow :: CreateTapeWithBarcode -> String
showsPrec :: Int -> CreateTapeWithBarcode -> ShowS
$cshowsPrec :: Int -> CreateTapeWithBarcode -> ShowS
Prelude.Show, forall x. Rep CreateTapeWithBarcode x -> CreateTapeWithBarcode
forall x. CreateTapeWithBarcode -> Rep CreateTapeWithBarcode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateTapeWithBarcode x -> CreateTapeWithBarcode
$cfrom :: forall x. CreateTapeWithBarcode -> Rep CreateTapeWithBarcode x
Prelude.Generic)

-- |
-- Create a value of 'CreateTapeWithBarcode' 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:
--
-- 'kmsEncrypted', 'createTapeWithBarcode_kmsEncrypted' - Set to @true@ to use Amazon S3 server-side encryption with your own KMS
-- key, or @false@ to use a key managed by Amazon S3. Optional.
--
-- Valid Values: @true@ | @false@
--
-- 'kmsKey', 'createTapeWithBarcode_kmsKey' - The Amazon Resource Name (ARN) of a symmetric customer master key (CMK)
-- used for Amazon S3 server-side encryption. Storage Gateway does not
-- support asymmetric CMKs. This value can only be set when @KMSEncrypted@
-- is @true@. Optional.
--
-- 'poolId', 'createTapeWithBarcode_poolId' - The ID of the pool that you want to add your tape to for archiving. The
-- tape in this pool is archived in the S3 storage class that is associated
-- with the pool. When you use your backup application to eject the tape,
-- the tape is archived directly into the storage class (S3 Glacier or S3
-- Deep Archive) that corresponds to the pool.
--
-- 'tags', 'createTapeWithBarcode_tags' - A list of up to 50 tags that can be assigned to a virtual tape that has
-- a barcode. Each tag is a key-value pair.
--
-- Valid characters for key and value are letters, spaces, and numbers
-- representable in UTF-8 format, and the following special characters: + -
-- = . _ : \/ \@. The maximum length of a tag\'s key is 128 characters, and
-- the maximum length for a tag\'s value is 256.
--
-- 'worm', 'createTapeWithBarcode_worm' - Set to @TRUE@ if the tape you are creating is to be configured as a
-- write-once-read-many (WORM) tape.
--
-- 'gatewayARN', 'createTapeWithBarcode_gatewayARN' - The unique Amazon Resource Name (ARN) that represents the gateway to
-- associate the virtual tape with. Use the ListGateways operation to
-- return a list of gateways for your account and Amazon Web Services
-- Region.
--
-- 'tapeSizeInBytes', 'createTapeWithBarcode_tapeSizeInBytes' - The size, in bytes, of the virtual tape that you want to create.
--
-- The size must be aligned by gigabyte (1024*1024*1024 bytes).
--
-- 'tapeBarcode', 'createTapeWithBarcode_tapeBarcode' - The barcode that you want to assign to the tape.
--
-- Barcodes cannot be reused. This includes barcodes used for tapes that
-- have been deleted.
newCreateTapeWithBarcode ::
  -- | 'gatewayARN'
  Prelude.Text ->
  -- | 'tapeSizeInBytes'
  Prelude.Integer ->
  -- | 'tapeBarcode'
  Prelude.Text ->
  CreateTapeWithBarcode
newCreateTapeWithBarcode :: Text -> Integer -> Text -> CreateTapeWithBarcode
newCreateTapeWithBarcode
  Text
pGatewayARN_
  Integer
pTapeSizeInBytes_
  Text
pTapeBarcode_ =
    CreateTapeWithBarcode'
      { $sel:kmsEncrypted:CreateTapeWithBarcode' :: Maybe Bool
kmsEncrypted =
          forall a. Maybe a
Prelude.Nothing,
        $sel:kmsKey:CreateTapeWithBarcode' :: Maybe Text
kmsKey = forall a. Maybe a
Prelude.Nothing,
        $sel:poolId:CreateTapeWithBarcode' :: Maybe Text
poolId = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateTapeWithBarcode' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:worm:CreateTapeWithBarcode' :: Maybe Bool
worm = forall a. Maybe a
Prelude.Nothing,
        $sel:gatewayARN:CreateTapeWithBarcode' :: Text
gatewayARN = Text
pGatewayARN_,
        $sel:tapeSizeInBytes:CreateTapeWithBarcode' :: Integer
tapeSizeInBytes = Integer
pTapeSizeInBytes_,
        $sel:tapeBarcode:CreateTapeWithBarcode' :: Text
tapeBarcode = Text
pTapeBarcode_
      }

-- | Set to @true@ to use Amazon S3 server-side encryption with your own KMS
-- key, or @false@ to use a key managed by Amazon S3. Optional.
--
-- Valid Values: @true@ | @false@
createTapeWithBarcode_kmsEncrypted :: Lens.Lens' CreateTapeWithBarcode (Prelude.Maybe Prelude.Bool)
createTapeWithBarcode_kmsEncrypted :: Lens' CreateTapeWithBarcode (Maybe Bool)
createTapeWithBarcode_kmsEncrypted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTapeWithBarcode' {Maybe Bool
kmsEncrypted :: Maybe Bool
$sel:kmsEncrypted:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Bool
kmsEncrypted} -> Maybe Bool
kmsEncrypted) (\s :: CreateTapeWithBarcode
s@CreateTapeWithBarcode' {} Maybe Bool
a -> CreateTapeWithBarcode
s {$sel:kmsEncrypted:CreateTapeWithBarcode' :: Maybe Bool
kmsEncrypted = Maybe Bool
a} :: CreateTapeWithBarcode)

-- | The Amazon Resource Name (ARN) of a symmetric customer master key (CMK)
-- used for Amazon S3 server-side encryption. Storage Gateway does not
-- support asymmetric CMKs. This value can only be set when @KMSEncrypted@
-- is @true@. Optional.
createTapeWithBarcode_kmsKey :: Lens.Lens' CreateTapeWithBarcode (Prelude.Maybe Prelude.Text)
createTapeWithBarcode_kmsKey :: Lens' CreateTapeWithBarcode (Maybe Text)
createTapeWithBarcode_kmsKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTapeWithBarcode' {Maybe Text
kmsKey :: Maybe Text
$sel:kmsKey:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Text
kmsKey} -> Maybe Text
kmsKey) (\s :: CreateTapeWithBarcode
s@CreateTapeWithBarcode' {} Maybe Text
a -> CreateTapeWithBarcode
s {$sel:kmsKey:CreateTapeWithBarcode' :: Maybe Text
kmsKey = Maybe Text
a} :: CreateTapeWithBarcode)

-- | The ID of the pool that you want to add your tape to for archiving. The
-- tape in this pool is archived in the S3 storage class that is associated
-- with the pool. When you use your backup application to eject the tape,
-- the tape is archived directly into the storage class (S3 Glacier or S3
-- Deep Archive) that corresponds to the pool.
createTapeWithBarcode_poolId :: Lens.Lens' CreateTapeWithBarcode (Prelude.Maybe Prelude.Text)
createTapeWithBarcode_poolId :: Lens' CreateTapeWithBarcode (Maybe Text)
createTapeWithBarcode_poolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTapeWithBarcode' {Maybe Text
poolId :: Maybe Text
$sel:poolId:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Text
poolId} -> Maybe Text
poolId) (\s :: CreateTapeWithBarcode
s@CreateTapeWithBarcode' {} Maybe Text
a -> CreateTapeWithBarcode
s {$sel:poolId:CreateTapeWithBarcode' :: Maybe Text
poolId = Maybe Text
a} :: CreateTapeWithBarcode)

-- | A list of up to 50 tags that can be assigned to a virtual tape that has
-- a barcode. Each tag is a key-value pair.
--
-- Valid characters for key and value are letters, spaces, and numbers
-- representable in UTF-8 format, and the following special characters: + -
-- = . _ : \/ \@. The maximum length of a tag\'s key is 128 characters, and
-- the maximum length for a tag\'s value is 256.
createTapeWithBarcode_tags :: Lens.Lens' CreateTapeWithBarcode (Prelude.Maybe [Tag])
createTapeWithBarcode_tags :: Lens' CreateTapeWithBarcode (Maybe [Tag])
createTapeWithBarcode_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTapeWithBarcode' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateTapeWithBarcode
s@CreateTapeWithBarcode' {} Maybe [Tag]
a -> CreateTapeWithBarcode
s {$sel:tags:CreateTapeWithBarcode' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateTapeWithBarcode) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Set to @TRUE@ if the tape you are creating is to be configured as a
-- write-once-read-many (WORM) tape.
createTapeWithBarcode_worm :: Lens.Lens' CreateTapeWithBarcode (Prelude.Maybe Prelude.Bool)
createTapeWithBarcode_worm :: Lens' CreateTapeWithBarcode (Maybe Bool)
createTapeWithBarcode_worm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTapeWithBarcode' {Maybe Bool
worm :: Maybe Bool
$sel:worm:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Bool
worm} -> Maybe Bool
worm) (\s :: CreateTapeWithBarcode
s@CreateTapeWithBarcode' {} Maybe Bool
a -> CreateTapeWithBarcode
s {$sel:worm:CreateTapeWithBarcode' :: Maybe Bool
worm = Maybe Bool
a} :: CreateTapeWithBarcode)

-- | The unique Amazon Resource Name (ARN) that represents the gateway to
-- associate the virtual tape with. Use the ListGateways operation to
-- return a list of gateways for your account and Amazon Web Services
-- Region.
createTapeWithBarcode_gatewayARN :: Lens.Lens' CreateTapeWithBarcode Prelude.Text
createTapeWithBarcode_gatewayARN :: Lens' CreateTapeWithBarcode Text
createTapeWithBarcode_gatewayARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTapeWithBarcode' {Text
gatewayARN :: Text
$sel:gatewayARN:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Text
gatewayARN} -> Text
gatewayARN) (\s :: CreateTapeWithBarcode
s@CreateTapeWithBarcode' {} Text
a -> CreateTapeWithBarcode
s {$sel:gatewayARN:CreateTapeWithBarcode' :: Text
gatewayARN = Text
a} :: CreateTapeWithBarcode)

-- | The size, in bytes, of the virtual tape that you want to create.
--
-- The size must be aligned by gigabyte (1024*1024*1024 bytes).
createTapeWithBarcode_tapeSizeInBytes :: Lens.Lens' CreateTapeWithBarcode Prelude.Integer
createTapeWithBarcode_tapeSizeInBytes :: Lens' CreateTapeWithBarcode Integer
createTapeWithBarcode_tapeSizeInBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTapeWithBarcode' {Integer
tapeSizeInBytes :: Integer
$sel:tapeSizeInBytes:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Integer
tapeSizeInBytes} -> Integer
tapeSizeInBytes) (\s :: CreateTapeWithBarcode
s@CreateTapeWithBarcode' {} Integer
a -> CreateTapeWithBarcode
s {$sel:tapeSizeInBytes:CreateTapeWithBarcode' :: Integer
tapeSizeInBytes = Integer
a} :: CreateTapeWithBarcode)

-- | The barcode that you want to assign to the tape.
--
-- Barcodes cannot be reused. This includes barcodes used for tapes that
-- have been deleted.
createTapeWithBarcode_tapeBarcode :: Lens.Lens' CreateTapeWithBarcode Prelude.Text
createTapeWithBarcode_tapeBarcode :: Lens' CreateTapeWithBarcode Text
createTapeWithBarcode_tapeBarcode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTapeWithBarcode' {Text
tapeBarcode :: Text
$sel:tapeBarcode:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Text
tapeBarcode} -> Text
tapeBarcode) (\s :: CreateTapeWithBarcode
s@CreateTapeWithBarcode' {} Text
a -> CreateTapeWithBarcode
s {$sel:tapeBarcode:CreateTapeWithBarcode' :: Text
tapeBarcode = Text
a} :: CreateTapeWithBarcode)

instance Core.AWSRequest CreateTapeWithBarcode where
  type
    AWSResponse CreateTapeWithBarcode =
      CreateTapeWithBarcodeResponse
  request :: (Service -> Service)
-> CreateTapeWithBarcode -> Request CreateTapeWithBarcode
request Service -> Service
overrides =
    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 CreateTapeWithBarcode
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateTapeWithBarcode)))
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 -> Int -> CreateTapeWithBarcodeResponse
CreateTapeWithBarcodeResponse'
            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
"TapeARN")
            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 CreateTapeWithBarcode where
  hashWithSalt :: Int -> CreateTapeWithBarcode -> Int
hashWithSalt Int
_salt CreateTapeWithBarcode' {Integer
Maybe Bool
Maybe [Tag]
Maybe Text
Text
tapeBarcode :: Text
tapeSizeInBytes :: Integer
gatewayARN :: Text
worm :: Maybe Bool
tags :: Maybe [Tag]
poolId :: Maybe Text
kmsKey :: Maybe Text
kmsEncrypted :: Maybe Bool
$sel:tapeBarcode:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Text
$sel:tapeSizeInBytes:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Integer
$sel:gatewayARN:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Text
$sel:worm:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Bool
$sel:tags:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe [Tag]
$sel:poolId:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Text
$sel:kmsKey:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Text
$sel:kmsEncrypted:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
kmsEncrypted
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
poolId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
worm
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gatewayARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Integer
tapeSizeInBytes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
tapeBarcode

instance Prelude.NFData CreateTapeWithBarcode where
  rnf :: CreateTapeWithBarcode -> ()
rnf CreateTapeWithBarcode' {Integer
Maybe Bool
Maybe [Tag]
Maybe Text
Text
tapeBarcode :: Text
tapeSizeInBytes :: Integer
gatewayARN :: Text
worm :: Maybe Bool
tags :: Maybe [Tag]
poolId :: Maybe Text
kmsKey :: Maybe Text
kmsEncrypted :: Maybe Bool
$sel:tapeBarcode:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Text
$sel:tapeSizeInBytes:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Integer
$sel:gatewayARN:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Text
$sel:worm:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Bool
$sel:tags:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe [Tag]
$sel:poolId:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Text
$sel:kmsKey:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Text
$sel:kmsEncrypted:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
kmsEncrypted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
poolId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
worm
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
gatewayARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Integer
tapeSizeInBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
tapeBarcode

instance Data.ToHeaders CreateTapeWithBarcode where
  toHeaders :: CreateTapeWithBarcode -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"StorageGateway_20130630.CreateTapeWithBarcode" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateTapeWithBarcode where
  toJSON :: CreateTapeWithBarcode -> Value
toJSON CreateTapeWithBarcode' {Integer
Maybe Bool
Maybe [Tag]
Maybe Text
Text
tapeBarcode :: Text
tapeSizeInBytes :: Integer
gatewayARN :: Text
worm :: Maybe Bool
tags :: Maybe [Tag]
poolId :: Maybe Text
kmsKey :: Maybe Text
kmsEncrypted :: Maybe Bool
$sel:tapeBarcode:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Text
$sel:tapeSizeInBytes:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Integer
$sel:gatewayARN:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Text
$sel:worm:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Bool
$sel:tags:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe [Tag]
$sel:poolId:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Text
$sel:kmsKey:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Text
$sel:kmsEncrypted:CreateTapeWithBarcode' :: CreateTapeWithBarcode -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"KMSEncrypted" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
kmsEncrypted,
            (Key
"KMSKey" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
kmsKey,
            (Key
"PoolId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
poolId,
            (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
            (Key
"Worm" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
worm,
            forall a. a -> Maybe a
Prelude.Just (Key
"GatewayARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
gatewayARN),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"TapeSizeInBytes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Integer
tapeSizeInBytes),
            forall a. a -> Maybe a
Prelude.Just (Key
"TapeBarcode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
tapeBarcode)
          ]
      )

instance Data.ToPath CreateTapeWithBarcode where
  toPath :: CreateTapeWithBarcode -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | CreateTapeOutput
--
-- /See:/ 'newCreateTapeWithBarcodeResponse' smart constructor.
data CreateTapeWithBarcodeResponse = CreateTapeWithBarcodeResponse'
  { -- | A unique Amazon Resource Name (ARN) that represents the virtual tape
    -- that was created.
    CreateTapeWithBarcodeResponse -> Maybe Text
tapeARN :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateTapeWithBarcodeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateTapeWithBarcodeResponse
-> CreateTapeWithBarcodeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateTapeWithBarcodeResponse
-> CreateTapeWithBarcodeResponse -> Bool
$c/= :: CreateTapeWithBarcodeResponse
-> CreateTapeWithBarcodeResponse -> Bool
== :: CreateTapeWithBarcodeResponse
-> CreateTapeWithBarcodeResponse -> Bool
$c== :: CreateTapeWithBarcodeResponse
-> CreateTapeWithBarcodeResponse -> Bool
Prelude.Eq, ReadPrec [CreateTapeWithBarcodeResponse]
ReadPrec CreateTapeWithBarcodeResponse
Int -> ReadS CreateTapeWithBarcodeResponse
ReadS [CreateTapeWithBarcodeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateTapeWithBarcodeResponse]
$creadListPrec :: ReadPrec [CreateTapeWithBarcodeResponse]
readPrec :: ReadPrec CreateTapeWithBarcodeResponse
$creadPrec :: ReadPrec CreateTapeWithBarcodeResponse
readList :: ReadS [CreateTapeWithBarcodeResponse]
$creadList :: ReadS [CreateTapeWithBarcodeResponse]
readsPrec :: Int -> ReadS CreateTapeWithBarcodeResponse
$creadsPrec :: Int -> ReadS CreateTapeWithBarcodeResponse
Prelude.Read, Int -> CreateTapeWithBarcodeResponse -> ShowS
[CreateTapeWithBarcodeResponse] -> ShowS
CreateTapeWithBarcodeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateTapeWithBarcodeResponse] -> ShowS
$cshowList :: [CreateTapeWithBarcodeResponse] -> ShowS
show :: CreateTapeWithBarcodeResponse -> String
$cshow :: CreateTapeWithBarcodeResponse -> String
showsPrec :: Int -> CreateTapeWithBarcodeResponse -> ShowS
$cshowsPrec :: Int -> CreateTapeWithBarcodeResponse -> ShowS
Prelude.Show, forall x.
Rep CreateTapeWithBarcodeResponse x
-> CreateTapeWithBarcodeResponse
forall x.
CreateTapeWithBarcodeResponse
-> Rep CreateTapeWithBarcodeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateTapeWithBarcodeResponse x
-> CreateTapeWithBarcodeResponse
$cfrom :: forall x.
CreateTapeWithBarcodeResponse
-> Rep CreateTapeWithBarcodeResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateTapeWithBarcodeResponse' 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:
--
-- 'tapeARN', 'createTapeWithBarcodeResponse_tapeARN' - A unique Amazon Resource Name (ARN) that represents the virtual tape
-- that was created.
--
-- 'httpStatus', 'createTapeWithBarcodeResponse_httpStatus' - The response's http status code.
newCreateTapeWithBarcodeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateTapeWithBarcodeResponse
newCreateTapeWithBarcodeResponse :: Int -> CreateTapeWithBarcodeResponse
newCreateTapeWithBarcodeResponse Int
pHttpStatus_ =
  CreateTapeWithBarcodeResponse'
    { $sel:tapeARN:CreateTapeWithBarcodeResponse' :: Maybe Text
tapeARN =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateTapeWithBarcodeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A unique Amazon Resource Name (ARN) that represents the virtual tape
-- that was created.
createTapeWithBarcodeResponse_tapeARN :: Lens.Lens' CreateTapeWithBarcodeResponse (Prelude.Maybe Prelude.Text)
createTapeWithBarcodeResponse_tapeARN :: Lens' CreateTapeWithBarcodeResponse (Maybe Text)
createTapeWithBarcodeResponse_tapeARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTapeWithBarcodeResponse' {Maybe Text
tapeARN :: Maybe Text
$sel:tapeARN:CreateTapeWithBarcodeResponse' :: CreateTapeWithBarcodeResponse -> Maybe Text
tapeARN} -> Maybe Text
tapeARN) (\s :: CreateTapeWithBarcodeResponse
s@CreateTapeWithBarcodeResponse' {} Maybe Text
a -> CreateTapeWithBarcodeResponse
s {$sel:tapeARN:CreateTapeWithBarcodeResponse' :: Maybe Text
tapeARN = Maybe Text
a} :: CreateTapeWithBarcodeResponse)

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

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