{-# 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.RetrieveTapeRecoveryPoint
-- 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 the recovery point for the specified virtual tape. This
-- operation is only supported in the tape gateway type.
--
-- A recovery point is a point in time view of a virtual tape at which all
-- the data on the tape is consistent. If your gateway crashes, virtual
-- tapes that have recovery points can be recovered to a new gateway.
--
-- The virtual tape can be retrieved to only one gateway. The retrieved
-- tape is read-only. The virtual tape can be retrieved to only a tape
-- gateway. There is no charge for retrieving recovery points.
module Amazonka.StorageGateway.RetrieveTapeRecoveryPoint
  ( -- * Creating a Request
    RetrieveTapeRecoveryPoint (..),
    newRetrieveTapeRecoveryPoint,

    -- * Request Lenses
    retrieveTapeRecoveryPoint_tapeARN,
    retrieveTapeRecoveryPoint_gatewayARN,

    -- * Destructuring the Response
    RetrieveTapeRecoveryPointResponse (..),
    newRetrieveTapeRecoveryPointResponse,

    -- * Response Lenses
    retrieveTapeRecoveryPointResponse_tapeARN,
    retrieveTapeRecoveryPointResponse_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

-- | RetrieveTapeRecoveryPointInput
--
-- /See:/ 'newRetrieveTapeRecoveryPoint' smart constructor.
data RetrieveTapeRecoveryPoint = RetrieveTapeRecoveryPoint'
  { -- | The Amazon Resource Name (ARN) of the virtual tape for which you want to
    -- retrieve the recovery point.
    RetrieveTapeRecoveryPoint -> Text
tapeARN :: Prelude.Text,
    RetrieveTapeRecoveryPoint -> Text
gatewayARN :: Prelude.Text
  }
  deriving (RetrieveTapeRecoveryPoint -> RetrieveTapeRecoveryPoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RetrieveTapeRecoveryPoint -> RetrieveTapeRecoveryPoint -> Bool
$c/= :: RetrieveTapeRecoveryPoint -> RetrieveTapeRecoveryPoint -> Bool
== :: RetrieveTapeRecoveryPoint -> RetrieveTapeRecoveryPoint -> Bool
$c== :: RetrieveTapeRecoveryPoint -> RetrieveTapeRecoveryPoint -> Bool
Prelude.Eq, ReadPrec [RetrieveTapeRecoveryPoint]
ReadPrec RetrieveTapeRecoveryPoint
Int -> ReadS RetrieveTapeRecoveryPoint
ReadS [RetrieveTapeRecoveryPoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RetrieveTapeRecoveryPoint]
$creadListPrec :: ReadPrec [RetrieveTapeRecoveryPoint]
readPrec :: ReadPrec RetrieveTapeRecoveryPoint
$creadPrec :: ReadPrec RetrieveTapeRecoveryPoint
readList :: ReadS [RetrieveTapeRecoveryPoint]
$creadList :: ReadS [RetrieveTapeRecoveryPoint]
readsPrec :: Int -> ReadS RetrieveTapeRecoveryPoint
$creadsPrec :: Int -> ReadS RetrieveTapeRecoveryPoint
Prelude.Read, Int -> RetrieveTapeRecoveryPoint -> ShowS
[RetrieveTapeRecoveryPoint] -> ShowS
RetrieveTapeRecoveryPoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RetrieveTapeRecoveryPoint] -> ShowS
$cshowList :: [RetrieveTapeRecoveryPoint] -> ShowS
show :: RetrieveTapeRecoveryPoint -> String
$cshow :: RetrieveTapeRecoveryPoint -> String
showsPrec :: Int -> RetrieveTapeRecoveryPoint -> ShowS
$cshowsPrec :: Int -> RetrieveTapeRecoveryPoint -> ShowS
Prelude.Show, forall x.
Rep RetrieveTapeRecoveryPoint x -> RetrieveTapeRecoveryPoint
forall x.
RetrieveTapeRecoveryPoint -> Rep RetrieveTapeRecoveryPoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RetrieveTapeRecoveryPoint x -> RetrieveTapeRecoveryPoint
$cfrom :: forall x.
RetrieveTapeRecoveryPoint -> Rep RetrieveTapeRecoveryPoint x
Prelude.Generic)

-- |
-- Create a value of 'RetrieveTapeRecoveryPoint' 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', 'retrieveTapeRecoveryPoint_tapeARN' - The Amazon Resource Name (ARN) of the virtual tape for which you want to
-- retrieve the recovery point.
--
-- 'gatewayARN', 'retrieveTapeRecoveryPoint_gatewayARN' - Undocumented member.
newRetrieveTapeRecoveryPoint ::
  -- | 'tapeARN'
  Prelude.Text ->
  -- | 'gatewayARN'
  Prelude.Text ->
  RetrieveTapeRecoveryPoint
newRetrieveTapeRecoveryPoint :: Text -> Text -> RetrieveTapeRecoveryPoint
newRetrieveTapeRecoveryPoint Text
pTapeARN_ Text
pGatewayARN_ =
  RetrieveTapeRecoveryPoint'
    { $sel:tapeARN:RetrieveTapeRecoveryPoint' :: Text
tapeARN = Text
pTapeARN_,
      $sel:gatewayARN:RetrieveTapeRecoveryPoint' :: Text
gatewayARN = Text
pGatewayARN_
    }

-- | The Amazon Resource Name (ARN) of the virtual tape for which you want to
-- retrieve the recovery point.
retrieveTapeRecoveryPoint_tapeARN :: Lens.Lens' RetrieveTapeRecoveryPoint Prelude.Text
retrieveTapeRecoveryPoint_tapeARN :: Lens' RetrieveTapeRecoveryPoint Text
retrieveTapeRecoveryPoint_tapeARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetrieveTapeRecoveryPoint' {Text
tapeARN :: Text
$sel:tapeARN:RetrieveTapeRecoveryPoint' :: RetrieveTapeRecoveryPoint -> Text
tapeARN} -> Text
tapeARN) (\s :: RetrieveTapeRecoveryPoint
s@RetrieveTapeRecoveryPoint' {} Text
a -> RetrieveTapeRecoveryPoint
s {$sel:tapeARN:RetrieveTapeRecoveryPoint' :: Text
tapeARN = Text
a} :: RetrieveTapeRecoveryPoint)

-- | Undocumented member.
retrieveTapeRecoveryPoint_gatewayARN :: Lens.Lens' RetrieveTapeRecoveryPoint Prelude.Text
retrieveTapeRecoveryPoint_gatewayARN :: Lens' RetrieveTapeRecoveryPoint Text
retrieveTapeRecoveryPoint_gatewayARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetrieveTapeRecoveryPoint' {Text
gatewayARN :: Text
$sel:gatewayARN:RetrieveTapeRecoveryPoint' :: RetrieveTapeRecoveryPoint -> Text
gatewayARN} -> Text
gatewayARN) (\s :: RetrieveTapeRecoveryPoint
s@RetrieveTapeRecoveryPoint' {} Text
a -> RetrieveTapeRecoveryPoint
s {$sel:gatewayARN:RetrieveTapeRecoveryPoint' :: Text
gatewayARN = Text
a} :: RetrieveTapeRecoveryPoint)

instance Core.AWSRequest RetrieveTapeRecoveryPoint where
  type
    AWSResponse RetrieveTapeRecoveryPoint =
      RetrieveTapeRecoveryPointResponse
  request :: (Service -> Service)
-> RetrieveTapeRecoveryPoint -> Request RetrieveTapeRecoveryPoint
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 RetrieveTapeRecoveryPoint
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RetrieveTapeRecoveryPoint)))
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 -> RetrieveTapeRecoveryPointResponse
RetrieveTapeRecoveryPointResponse'
            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 RetrieveTapeRecoveryPoint where
  hashWithSalt :: Int -> RetrieveTapeRecoveryPoint -> Int
hashWithSalt Int
_salt RetrieveTapeRecoveryPoint' {Text
gatewayARN :: Text
tapeARN :: Text
$sel:gatewayARN:RetrieveTapeRecoveryPoint' :: RetrieveTapeRecoveryPoint -> Text
$sel:tapeARN:RetrieveTapeRecoveryPoint' :: RetrieveTapeRecoveryPoint -> 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 RetrieveTapeRecoveryPoint where
  rnf :: RetrieveTapeRecoveryPoint -> ()
rnf RetrieveTapeRecoveryPoint' {Text
gatewayARN :: Text
tapeARN :: Text
$sel:gatewayARN:RetrieveTapeRecoveryPoint' :: RetrieveTapeRecoveryPoint -> Text
$sel:tapeARN:RetrieveTapeRecoveryPoint' :: RetrieveTapeRecoveryPoint -> 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 RetrieveTapeRecoveryPoint where
  toHeaders :: RetrieveTapeRecoveryPoint -> 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.RetrieveTapeRecoveryPoint" ::
                          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 RetrieveTapeRecoveryPoint where
  toJSON :: RetrieveTapeRecoveryPoint -> Value
toJSON RetrieveTapeRecoveryPoint' {Text
gatewayARN :: Text
tapeARN :: Text
$sel:gatewayARN:RetrieveTapeRecoveryPoint' :: RetrieveTapeRecoveryPoint -> Text
$sel:tapeARN:RetrieveTapeRecoveryPoint' :: RetrieveTapeRecoveryPoint -> 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 RetrieveTapeRecoveryPoint where
  toPath :: RetrieveTapeRecoveryPoint -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'RetrieveTapeRecoveryPointResponse' 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', 'retrieveTapeRecoveryPointResponse_tapeARN' - The Amazon Resource Name (ARN) of the virtual tape for which the
-- recovery point was retrieved.
--
-- 'httpStatus', 'retrieveTapeRecoveryPointResponse_httpStatus' - The response's http status code.
newRetrieveTapeRecoveryPointResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RetrieveTapeRecoveryPointResponse
newRetrieveTapeRecoveryPointResponse :: Int -> RetrieveTapeRecoveryPointResponse
newRetrieveTapeRecoveryPointResponse Int
pHttpStatus_ =
  RetrieveTapeRecoveryPointResponse'
    { $sel:tapeARN:RetrieveTapeRecoveryPointResponse' :: Maybe Text
tapeARN =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RetrieveTapeRecoveryPointResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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