{-# 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.AssignTapePool
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Assigns a tape to a tape pool for archiving. The tape assigned to a 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 S3 storage class (S3 Glacier or S3 Glacier
-- Deep Archive) that corresponds to the pool.
module Amazonka.StorageGateway.AssignTapePool
  ( -- * Creating a Request
    AssignTapePool (..),
    newAssignTapePool,

    -- * Request Lenses
    assignTapePool_bypassGovernanceRetention,
    assignTapePool_tapeARN,
    assignTapePool_poolId,

    -- * Destructuring the Response
    AssignTapePoolResponse (..),
    newAssignTapePoolResponse,

    -- * Response Lenses
    assignTapePoolResponse_tapeARN,
    assignTapePoolResponse_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

-- | /See:/ 'newAssignTapePool' smart constructor.
data AssignTapePool = AssignTapePool'
  { -- | Set permissions to bypass governance retention. If the lock type of the
    -- archived tape is @Governance@, the tape\'s archived age is not older
    -- than @RetentionLockInDays@, and the user does not already have
    -- @BypassGovernanceRetention@, setting this to TRUE enables the user to
    -- bypass the retention lock. This parameter is set to true by default for
    -- calls from the console.
    --
    -- Valid values: @TRUE@ | @FALSE@
    AssignTapePool -> Maybe Bool
bypassGovernanceRetention :: Prelude.Maybe Prelude.Bool,
    -- | The unique Amazon Resource Name (ARN) of the virtual tape that you want
    -- to add to the tape pool.
    AssignTapePool -> Text
tapeARN :: 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
    -- Glacier Deep Archive) that corresponds to the pool.
    AssignTapePool -> Text
poolId :: Prelude.Text
  }
  deriving (AssignTapePool -> AssignTapePool -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssignTapePool -> AssignTapePool -> Bool
$c/= :: AssignTapePool -> AssignTapePool -> Bool
== :: AssignTapePool -> AssignTapePool -> Bool
$c== :: AssignTapePool -> AssignTapePool -> Bool
Prelude.Eq, ReadPrec [AssignTapePool]
ReadPrec AssignTapePool
Int -> ReadS AssignTapePool
ReadS [AssignTapePool]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssignTapePool]
$creadListPrec :: ReadPrec [AssignTapePool]
readPrec :: ReadPrec AssignTapePool
$creadPrec :: ReadPrec AssignTapePool
readList :: ReadS [AssignTapePool]
$creadList :: ReadS [AssignTapePool]
readsPrec :: Int -> ReadS AssignTapePool
$creadsPrec :: Int -> ReadS AssignTapePool
Prelude.Read, Int -> AssignTapePool -> ShowS
[AssignTapePool] -> ShowS
AssignTapePool -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssignTapePool] -> ShowS
$cshowList :: [AssignTapePool] -> ShowS
show :: AssignTapePool -> String
$cshow :: AssignTapePool -> String
showsPrec :: Int -> AssignTapePool -> ShowS
$cshowsPrec :: Int -> AssignTapePool -> ShowS
Prelude.Show, forall x. Rep AssignTapePool x -> AssignTapePool
forall x. AssignTapePool -> Rep AssignTapePool x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssignTapePool x -> AssignTapePool
$cfrom :: forall x. AssignTapePool -> Rep AssignTapePool x
Prelude.Generic)

-- |
-- Create a value of 'AssignTapePool' 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:
--
-- 'bypassGovernanceRetention', 'assignTapePool_bypassGovernanceRetention' - Set permissions to bypass governance retention. If the lock type of the
-- archived tape is @Governance@, the tape\'s archived age is not older
-- than @RetentionLockInDays@, and the user does not already have
-- @BypassGovernanceRetention@, setting this to TRUE enables the user to
-- bypass the retention lock. This parameter is set to true by default for
-- calls from the console.
--
-- Valid values: @TRUE@ | @FALSE@
--
-- 'tapeARN', 'assignTapePool_tapeARN' - The unique Amazon Resource Name (ARN) of the virtual tape that you want
-- to add to the tape pool.
--
-- 'poolId', 'assignTapePool_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
-- Glacier Deep Archive) that corresponds to the pool.
newAssignTapePool ::
  -- | 'tapeARN'
  Prelude.Text ->
  -- | 'poolId'
  Prelude.Text ->
  AssignTapePool
newAssignTapePool :: Text -> Text -> AssignTapePool
newAssignTapePool Text
pTapeARN_ Text
pPoolId_ =
  AssignTapePool'
    { $sel:bypassGovernanceRetention:AssignTapePool' :: Maybe Bool
bypassGovernanceRetention =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tapeARN:AssignTapePool' :: Text
tapeARN = Text
pTapeARN_,
      $sel:poolId:AssignTapePool' :: Text
poolId = Text
pPoolId_
    }

-- | Set permissions to bypass governance retention. If the lock type of the
-- archived tape is @Governance@, the tape\'s archived age is not older
-- than @RetentionLockInDays@, and the user does not already have
-- @BypassGovernanceRetention@, setting this to TRUE enables the user to
-- bypass the retention lock. This parameter is set to true by default for
-- calls from the console.
--
-- Valid values: @TRUE@ | @FALSE@
assignTapePool_bypassGovernanceRetention :: Lens.Lens' AssignTapePool (Prelude.Maybe Prelude.Bool)
assignTapePool_bypassGovernanceRetention :: Lens' AssignTapePool (Maybe Bool)
assignTapePool_bypassGovernanceRetention = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssignTapePool' {Maybe Bool
bypassGovernanceRetention :: Maybe Bool
$sel:bypassGovernanceRetention:AssignTapePool' :: AssignTapePool -> Maybe Bool
bypassGovernanceRetention} -> Maybe Bool
bypassGovernanceRetention) (\s :: AssignTapePool
s@AssignTapePool' {} Maybe Bool
a -> AssignTapePool
s {$sel:bypassGovernanceRetention:AssignTapePool' :: Maybe Bool
bypassGovernanceRetention = Maybe Bool
a} :: AssignTapePool)

-- | The unique Amazon Resource Name (ARN) of the virtual tape that you want
-- to add to the tape pool.
assignTapePool_tapeARN :: Lens.Lens' AssignTapePool Prelude.Text
assignTapePool_tapeARN :: Lens' AssignTapePool Text
assignTapePool_tapeARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssignTapePool' {Text
tapeARN :: Text
$sel:tapeARN:AssignTapePool' :: AssignTapePool -> Text
tapeARN} -> Text
tapeARN) (\s :: AssignTapePool
s@AssignTapePool' {} Text
a -> AssignTapePool
s {$sel:tapeARN:AssignTapePool' :: Text
tapeARN = Text
a} :: AssignTapePool)

-- | 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
-- Glacier Deep Archive) that corresponds to the pool.
assignTapePool_poolId :: Lens.Lens' AssignTapePool Prelude.Text
assignTapePool_poolId :: Lens' AssignTapePool Text
assignTapePool_poolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssignTapePool' {Text
poolId :: Text
$sel:poolId:AssignTapePool' :: AssignTapePool -> Text
poolId} -> Text
poolId) (\s :: AssignTapePool
s@AssignTapePool' {} Text
a -> AssignTapePool
s {$sel:poolId:AssignTapePool' :: Text
poolId = Text
a} :: AssignTapePool)

instance Core.AWSRequest AssignTapePool where
  type
    AWSResponse AssignTapePool =
      AssignTapePoolResponse
  request :: (Service -> Service) -> AssignTapePool -> Request AssignTapePool
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 AssignTapePool
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AssignTapePool)))
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 -> AssignTapePoolResponse
AssignTapePoolResponse'
            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 AssignTapePool where
  hashWithSalt :: Int -> AssignTapePool -> Int
hashWithSalt Int
_salt AssignTapePool' {Maybe Bool
Text
poolId :: Text
tapeARN :: Text
bypassGovernanceRetention :: Maybe Bool
$sel:poolId:AssignTapePool' :: AssignTapePool -> Text
$sel:tapeARN:AssignTapePool' :: AssignTapePool -> Text
$sel:bypassGovernanceRetention:AssignTapePool' :: AssignTapePool -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
bypassGovernanceRetention
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
tapeARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
poolId

instance Prelude.NFData AssignTapePool where
  rnf :: AssignTapePool -> ()
rnf AssignTapePool' {Maybe Bool
Text
poolId :: Text
tapeARN :: Text
bypassGovernanceRetention :: Maybe Bool
$sel:poolId:AssignTapePool' :: AssignTapePool -> Text
$sel:tapeARN:AssignTapePool' :: AssignTapePool -> Text
$sel:bypassGovernanceRetention:AssignTapePool' :: AssignTapePool -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
bypassGovernanceRetention
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
tapeARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
poolId

instance Data.ToHeaders AssignTapePool where
  toHeaders :: AssignTapePool -> 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.AssignTapePool" ::
                          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 AssignTapePool where
  toJSON :: AssignTapePool -> Value
toJSON AssignTapePool' {Maybe Bool
Text
poolId :: Text
tapeARN :: Text
bypassGovernanceRetention :: Maybe Bool
$sel:poolId:AssignTapePool' :: AssignTapePool -> Text
$sel:tapeARN:AssignTapePool' :: AssignTapePool -> Text
$sel:bypassGovernanceRetention:AssignTapePool' :: AssignTapePool -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"BypassGovernanceRetention" 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
bypassGovernanceRetention,
            forall a. a -> Maybe a
Prelude.Just (Key
"TapeARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
tapeARN),
            forall a. a -> Maybe a
Prelude.Just (Key
"PoolId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
poolId)
          ]
      )

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

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

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

-- |
-- Create a value of 'AssignTapePoolResponse' 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', 'assignTapePoolResponse_tapeARN' - The unique Amazon Resource Names (ARN) of the virtual tape that was
-- added to the tape pool.
--
-- 'httpStatus', 'assignTapePoolResponse_httpStatus' - The response's http status code.
newAssignTapePoolResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AssignTapePoolResponse
newAssignTapePoolResponse :: Int -> AssignTapePoolResponse
newAssignTapePoolResponse Int
pHttpStatus_ =
  AssignTapePoolResponse'
    { $sel:tapeARN:AssignTapePoolResponse' :: Maybe Text
tapeARN = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AssignTapePoolResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The unique Amazon Resource Names (ARN) of the virtual tape that was
-- added to the tape pool.
assignTapePoolResponse_tapeARN :: Lens.Lens' AssignTapePoolResponse (Prelude.Maybe Prelude.Text)
assignTapePoolResponse_tapeARN :: Lens' AssignTapePoolResponse (Maybe Text)
assignTapePoolResponse_tapeARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssignTapePoolResponse' {Maybe Text
tapeARN :: Maybe Text
$sel:tapeARN:AssignTapePoolResponse' :: AssignTapePoolResponse -> Maybe Text
tapeARN} -> Maybe Text
tapeARN) (\s :: AssignTapePoolResponse
s@AssignTapePoolResponse' {} Maybe Text
a -> AssignTapePoolResponse
s {$sel:tapeARN:AssignTapePoolResponse' :: Maybe Text
tapeARN = Maybe Text
a} :: AssignTapePoolResponse)

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

instance Prelude.NFData AssignTapePoolResponse where
  rnf :: AssignTapePoolResponse -> ()
rnf AssignTapePoolResponse' {Int
Maybe Text
httpStatus :: Int
tapeARN :: Maybe Text
$sel:httpStatus:AssignTapePoolResponse' :: AssignTapePoolResponse -> Int
$sel:tapeARN:AssignTapePoolResponse' :: AssignTapePoolResponse -> 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