{-# 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.RetrieveTapeArchive
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves an archived virtual tape from the virtual tape shelf (VTS) to
-- a tape gateway. Virtual tapes archived in the VTS are not associated
-- with any gateway. However after a tape is retrieved, it is associated
-- with a gateway, even though it is also listed in the VTS, that is,
-- archive. This operation is only supported in the tape gateway type.
--
-- Once a tape is successfully retrieved to a gateway, it cannot be
-- retrieved again to another gateway. You must archive the tape again
-- before you can retrieve it to another gateway. This operation is only
-- supported in the tape gateway type.
module Amazonka.StorageGateway.RetrieveTapeArchive
  ( -- * Creating a Request
    RetrieveTapeArchive (..),
    newRetrieveTapeArchive,

    -- * Request Lenses
    retrieveTapeArchive_tapeARN,
    retrieveTapeArchive_gatewayARN,

    -- * Destructuring the Response
    RetrieveTapeArchiveResponse (..),
    newRetrieveTapeArchiveResponse,

    -- * Response Lenses
    retrieveTapeArchiveResponse_tapeARN,
    retrieveTapeArchiveResponse_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

-- | RetrieveTapeArchiveInput
--
-- /See:/ 'newRetrieveTapeArchive' smart constructor.
data RetrieveTapeArchive = RetrieveTapeArchive'
  { -- | The Amazon Resource Name (ARN) of the virtual tape you want to retrieve
    -- from the virtual tape shelf (VTS).
    RetrieveTapeArchive -> Text
tapeARN :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the gateway you want to retrieve the
    -- virtual tape to. Use the ListGateways operation to return a list of
    -- gateways for your account and Amazon Web Services Region.
    --
    -- You retrieve archived virtual tapes to only one gateway and the gateway
    -- must be a tape gateway.
    RetrieveTapeArchive -> Text
gatewayARN :: Prelude.Text
  }
  deriving (RetrieveTapeArchive -> RetrieveTapeArchive -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RetrieveTapeArchive -> RetrieveTapeArchive -> Bool
$c/= :: RetrieveTapeArchive -> RetrieveTapeArchive -> Bool
== :: RetrieveTapeArchive -> RetrieveTapeArchive -> Bool
$c== :: RetrieveTapeArchive -> RetrieveTapeArchive -> Bool
Prelude.Eq, ReadPrec [RetrieveTapeArchive]
ReadPrec RetrieveTapeArchive
Int -> ReadS RetrieveTapeArchive
ReadS [RetrieveTapeArchive]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RetrieveTapeArchive]
$creadListPrec :: ReadPrec [RetrieveTapeArchive]
readPrec :: ReadPrec RetrieveTapeArchive
$creadPrec :: ReadPrec RetrieveTapeArchive
readList :: ReadS [RetrieveTapeArchive]
$creadList :: ReadS [RetrieveTapeArchive]
readsPrec :: Int -> ReadS RetrieveTapeArchive
$creadsPrec :: Int -> ReadS RetrieveTapeArchive
Prelude.Read, Int -> RetrieveTapeArchive -> ShowS
[RetrieveTapeArchive] -> ShowS
RetrieveTapeArchive -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RetrieveTapeArchive] -> ShowS
$cshowList :: [RetrieveTapeArchive] -> ShowS
show :: RetrieveTapeArchive -> String
$cshow :: RetrieveTapeArchive -> String
showsPrec :: Int -> RetrieveTapeArchive -> ShowS
$cshowsPrec :: Int -> RetrieveTapeArchive -> ShowS
Prelude.Show, forall x. Rep RetrieveTapeArchive x -> RetrieveTapeArchive
forall x. RetrieveTapeArchive -> Rep RetrieveTapeArchive x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RetrieveTapeArchive x -> RetrieveTapeArchive
$cfrom :: forall x. RetrieveTapeArchive -> Rep RetrieveTapeArchive x
Prelude.Generic)

-- |
-- Create a value of 'RetrieveTapeArchive' 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', 'retrieveTapeArchive_tapeARN' - The Amazon Resource Name (ARN) of the virtual tape you want to retrieve
-- from the virtual tape shelf (VTS).
--
-- 'gatewayARN', 'retrieveTapeArchive_gatewayARN' - The Amazon Resource Name (ARN) of the gateway you want to retrieve the
-- virtual tape to. Use the ListGateways operation to return a list of
-- gateways for your account and Amazon Web Services Region.
--
-- You retrieve archived virtual tapes to only one gateway and the gateway
-- must be a tape gateway.
newRetrieveTapeArchive ::
  -- | 'tapeARN'
  Prelude.Text ->
  -- | 'gatewayARN'
  Prelude.Text ->
  RetrieveTapeArchive
newRetrieveTapeArchive :: Text -> Text -> RetrieveTapeArchive
newRetrieveTapeArchive Text
pTapeARN_ Text
pGatewayARN_ =
  RetrieveTapeArchive'
    { $sel:tapeARN:RetrieveTapeArchive' :: Text
tapeARN = Text
pTapeARN_,
      $sel:gatewayARN:RetrieveTapeArchive' :: Text
gatewayARN = Text
pGatewayARN_
    }

-- | The Amazon Resource Name (ARN) of the virtual tape you want to retrieve
-- from the virtual tape shelf (VTS).
retrieveTapeArchive_tapeARN :: Lens.Lens' RetrieveTapeArchive Prelude.Text
retrieveTapeArchive_tapeARN :: Lens' RetrieveTapeArchive Text
retrieveTapeArchive_tapeARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetrieveTapeArchive' {Text
tapeARN :: Text
$sel:tapeARN:RetrieveTapeArchive' :: RetrieveTapeArchive -> Text
tapeARN} -> Text
tapeARN) (\s :: RetrieveTapeArchive
s@RetrieveTapeArchive' {} Text
a -> RetrieveTapeArchive
s {$sel:tapeARN:RetrieveTapeArchive' :: Text
tapeARN = Text
a} :: RetrieveTapeArchive)

-- | The Amazon Resource Name (ARN) of the gateway you want to retrieve the
-- virtual tape to. Use the ListGateways operation to return a list of
-- gateways for your account and Amazon Web Services Region.
--
-- You retrieve archived virtual tapes to only one gateway and the gateway
-- must be a tape gateway.
retrieveTapeArchive_gatewayARN :: Lens.Lens' RetrieveTapeArchive Prelude.Text
retrieveTapeArchive_gatewayARN :: Lens' RetrieveTapeArchive Text
retrieveTapeArchive_gatewayARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetrieveTapeArchive' {Text
gatewayARN :: Text
$sel:gatewayARN:RetrieveTapeArchive' :: RetrieveTapeArchive -> Text
gatewayARN} -> Text
gatewayARN) (\s :: RetrieveTapeArchive
s@RetrieveTapeArchive' {} Text
a -> RetrieveTapeArchive
s {$sel:gatewayARN:RetrieveTapeArchive' :: Text
gatewayARN = Text
a} :: RetrieveTapeArchive)

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

instance Prelude.NFData RetrieveTapeArchive where
  rnf :: RetrieveTapeArchive -> ()
rnf RetrieveTapeArchive' {Text
gatewayARN :: Text
tapeARN :: Text
$sel:gatewayARN:RetrieveTapeArchive' :: RetrieveTapeArchive -> Text
$sel:tapeARN:RetrieveTapeArchive' :: RetrieveTapeArchive -> Text
..} =
    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
gatewayARN

instance Data.ToHeaders RetrieveTapeArchive where
  toHeaders :: RetrieveTapeArchive -> 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.RetrieveTapeArchive" ::
                          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 RetrieveTapeArchive where
  toJSON :: RetrieveTapeArchive -> Value
toJSON RetrieveTapeArchive' {Text
gatewayARN :: Text
tapeARN :: Text
$sel:gatewayARN:RetrieveTapeArchive' :: RetrieveTapeArchive -> Text
$sel:tapeARN:RetrieveTapeArchive' :: RetrieveTapeArchive -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ 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
"GatewayARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
gatewayARN)
          ]
      )

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

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

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

-- |
-- Create a value of 'RetrieveTapeArchiveResponse' 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', 'retrieveTapeArchiveResponse_tapeARN' - The Amazon Resource Name (ARN) of the retrieved virtual tape.
--
-- 'httpStatus', 'retrieveTapeArchiveResponse_httpStatus' - The response's http status code.
newRetrieveTapeArchiveResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RetrieveTapeArchiveResponse
newRetrieveTapeArchiveResponse :: Int -> RetrieveTapeArchiveResponse
newRetrieveTapeArchiveResponse Int
pHttpStatus_ =
  RetrieveTapeArchiveResponse'
    { $sel:tapeARN:RetrieveTapeArchiveResponse' :: Maybe Text
tapeARN =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RetrieveTapeArchiveResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the retrieved virtual tape.
retrieveTapeArchiveResponse_tapeARN :: Lens.Lens' RetrieveTapeArchiveResponse (Prelude.Maybe Prelude.Text)
retrieveTapeArchiveResponse_tapeARN :: Lens' RetrieveTapeArchiveResponse (Maybe Text)
retrieveTapeArchiveResponse_tapeARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetrieveTapeArchiveResponse' {Maybe Text
tapeARN :: Maybe Text
$sel:tapeARN:RetrieveTapeArchiveResponse' :: RetrieveTapeArchiveResponse -> Maybe Text
tapeARN} -> Maybe Text
tapeARN) (\s :: RetrieveTapeArchiveResponse
s@RetrieveTapeArchiveResponse' {} Maybe Text
a -> RetrieveTapeArchiveResponse
s {$sel:tapeARN:RetrieveTapeArchiveResponse' :: Maybe Text
tapeARN = Maybe Text
a} :: RetrieveTapeArchiveResponse)

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

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