{-# 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.EC2.RestoreSnapshotTier
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Restores an archived Amazon EBS snapshot for use temporarily or
-- permanently, or modifies the restore period or restore type for a
-- snapshot that was previously temporarily restored.
--
-- For more information see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/working-with-snapshot-archiving.html#restore-archived-snapshot Restore an archived snapshot>
-- and
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/working-with-snapshot-archiving.html#modify-temp-restore-period modify the restore period or restore type for a temporarily restored snapshot>
-- in the /Amazon Elastic Compute Cloud User Guide/.
module Amazonka.EC2.RestoreSnapshotTier
  ( -- * Creating a Request
    RestoreSnapshotTier (..),
    newRestoreSnapshotTier,

    -- * Request Lenses
    restoreSnapshotTier_dryRun,
    restoreSnapshotTier_permanentRestore,
    restoreSnapshotTier_temporaryRestoreDays,
    restoreSnapshotTier_snapshotId,

    -- * Destructuring the Response
    RestoreSnapshotTierResponse (..),
    newRestoreSnapshotTierResponse,

    -- * Response Lenses
    restoreSnapshotTierResponse_isPermanentRestore,
    restoreSnapshotTierResponse_restoreDuration,
    restoreSnapshotTierResponse_restoreStartTime,
    restoreSnapshotTierResponse_snapshotId,
    restoreSnapshotTierResponse_httpStatus,
  )
where

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

-- | /See:/ 'newRestoreSnapshotTier' smart constructor.
data RestoreSnapshotTier = RestoreSnapshotTier'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    RestoreSnapshotTier -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether to permanently restore an archived snapshot. To
    -- permanently restore an archived snapshot, specify @true@ and omit the
    -- __RestoreSnapshotTierRequest$TemporaryRestoreDays__ parameter.
    RestoreSnapshotTier -> Maybe Bool
permanentRestore :: Prelude.Maybe Prelude.Bool,
    -- | Specifies the number of days for which to temporarily restore an
    -- archived snapshot. Required for temporary restores only. The snapshot
    -- will be automatically re-archived after this period.
    --
    -- To temporarily restore an archived snapshot, specify the number of days
    -- and omit the __PermanentRestore__ parameter or set it to @false@.
    RestoreSnapshotTier -> Maybe Int
temporaryRestoreDays :: Prelude.Maybe Prelude.Int,
    -- | The ID of the snapshot to restore.
    RestoreSnapshotTier -> Text
snapshotId :: Prelude.Text
  }
  deriving (RestoreSnapshotTier -> RestoreSnapshotTier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreSnapshotTier -> RestoreSnapshotTier -> Bool
$c/= :: RestoreSnapshotTier -> RestoreSnapshotTier -> Bool
== :: RestoreSnapshotTier -> RestoreSnapshotTier -> Bool
$c== :: RestoreSnapshotTier -> RestoreSnapshotTier -> Bool
Prelude.Eq, ReadPrec [RestoreSnapshotTier]
ReadPrec RestoreSnapshotTier
Int -> ReadS RestoreSnapshotTier
ReadS [RestoreSnapshotTier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestoreSnapshotTier]
$creadListPrec :: ReadPrec [RestoreSnapshotTier]
readPrec :: ReadPrec RestoreSnapshotTier
$creadPrec :: ReadPrec RestoreSnapshotTier
readList :: ReadS [RestoreSnapshotTier]
$creadList :: ReadS [RestoreSnapshotTier]
readsPrec :: Int -> ReadS RestoreSnapshotTier
$creadsPrec :: Int -> ReadS RestoreSnapshotTier
Prelude.Read, Int -> RestoreSnapshotTier -> ShowS
[RestoreSnapshotTier] -> ShowS
RestoreSnapshotTier -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreSnapshotTier] -> ShowS
$cshowList :: [RestoreSnapshotTier] -> ShowS
show :: RestoreSnapshotTier -> String
$cshow :: RestoreSnapshotTier -> String
showsPrec :: Int -> RestoreSnapshotTier -> ShowS
$cshowsPrec :: Int -> RestoreSnapshotTier -> ShowS
Prelude.Show, forall x. Rep RestoreSnapshotTier x -> RestoreSnapshotTier
forall x. RestoreSnapshotTier -> Rep RestoreSnapshotTier x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RestoreSnapshotTier x -> RestoreSnapshotTier
$cfrom :: forall x. RestoreSnapshotTier -> Rep RestoreSnapshotTier x
Prelude.Generic)

-- |
-- Create a value of 'RestoreSnapshotTier' 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:
--
-- 'dryRun', 'restoreSnapshotTier_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'permanentRestore', 'restoreSnapshotTier_permanentRestore' - Indicates whether to permanently restore an archived snapshot. To
-- permanently restore an archived snapshot, specify @true@ and omit the
-- __RestoreSnapshotTierRequest$TemporaryRestoreDays__ parameter.
--
-- 'temporaryRestoreDays', 'restoreSnapshotTier_temporaryRestoreDays' - Specifies the number of days for which to temporarily restore an
-- archived snapshot. Required for temporary restores only. The snapshot
-- will be automatically re-archived after this period.
--
-- To temporarily restore an archived snapshot, specify the number of days
-- and omit the __PermanentRestore__ parameter or set it to @false@.
--
-- 'snapshotId', 'restoreSnapshotTier_snapshotId' - The ID of the snapshot to restore.
newRestoreSnapshotTier ::
  -- | 'snapshotId'
  Prelude.Text ->
  RestoreSnapshotTier
newRestoreSnapshotTier :: Text -> RestoreSnapshotTier
newRestoreSnapshotTier Text
pSnapshotId_ =
  RestoreSnapshotTier'
    { $sel:dryRun:RestoreSnapshotTier' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:permanentRestore:RestoreSnapshotTier' :: Maybe Bool
permanentRestore = forall a. Maybe a
Prelude.Nothing,
      $sel:temporaryRestoreDays:RestoreSnapshotTier' :: Maybe Int
temporaryRestoreDays = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotId:RestoreSnapshotTier' :: Text
snapshotId = Text
pSnapshotId_
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
restoreSnapshotTier_dryRun :: Lens.Lens' RestoreSnapshotTier (Prelude.Maybe Prelude.Bool)
restoreSnapshotTier_dryRun :: Lens' RestoreSnapshotTier (Maybe Bool)
restoreSnapshotTier_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreSnapshotTier' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: RestoreSnapshotTier
s@RestoreSnapshotTier' {} Maybe Bool
a -> RestoreSnapshotTier
s {$sel:dryRun:RestoreSnapshotTier' :: Maybe Bool
dryRun = Maybe Bool
a} :: RestoreSnapshotTier)

-- | Indicates whether to permanently restore an archived snapshot. To
-- permanently restore an archived snapshot, specify @true@ and omit the
-- __RestoreSnapshotTierRequest$TemporaryRestoreDays__ parameter.
restoreSnapshotTier_permanentRestore :: Lens.Lens' RestoreSnapshotTier (Prelude.Maybe Prelude.Bool)
restoreSnapshotTier_permanentRestore :: Lens' RestoreSnapshotTier (Maybe Bool)
restoreSnapshotTier_permanentRestore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreSnapshotTier' {Maybe Bool
permanentRestore :: Maybe Bool
$sel:permanentRestore:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Bool
permanentRestore} -> Maybe Bool
permanentRestore) (\s :: RestoreSnapshotTier
s@RestoreSnapshotTier' {} Maybe Bool
a -> RestoreSnapshotTier
s {$sel:permanentRestore:RestoreSnapshotTier' :: Maybe Bool
permanentRestore = Maybe Bool
a} :: RestoreSnapshotTier)

-- | Specifies the number of days for which to temporarily restore an
-- archived snapshot. Required for temporary restores only. The snapshot
-- will be automatically re-archived after this period.
--
-- To temporarily restore an archived snapshot, specify the number of days
-- and omit the __PermanentRestore__ parameter or set it to @false@.
restoreSnapshotTier_temporaryRestoreDays :: Lens.Lens' RestoreSnapshotTier (Prelude.Maybe Prelude.Int)
restoreSnapshotTier_temporaryRestoreDays :: Lens' RestoreSnapshotTier (Maybe Int)
restoreSnapshotTier_temporaryRestoreDays = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreSnapshotTier' {Maybe Int
temporaryRestoreDays :: Maybe Int
$sel:temporaryRestoreDays:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Int
temporaryRestoreDays} -> Maybe Int
temporaryRestoreDays) (\s :: RestoreSnapshotTier
s@RestoreSnapshotTier' {} Maybe Int
a -> RestoreSnapshotTier
s {$sel:temporaryRestoreDays:RestoreSnapshotTier' :: Maybe Int
temporaryRestoreDays = Maybe Int
a} :: RestoreSnapshotTier)

-- | The ID of the snapshot to restore.
restoreSnapshotTier_snapshotId :: Lens.Lens' RestoreSnapshotTier Prelude.Text
restoreSnapshotTier_snapshotId :: Lens' RestoreSnapshotTier Text
restoreSnapshotTier_snapshotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreSnapshotTier' {Text
snapshotId :: Text
$sel:snapshotId:RestoreSnapshotTier' :: RestoreSnapshotTier -> Text
snapshotId} -> Text
snapshotId) (\s :: RestoreSnapshotTier
s@RestoreSnapshotTier' {} Text
a -> RestoreSnapshotTier
s {$sel:snapshotId:RestoreSnapshotTier' :: Text
snapshotId = Text
a} :: RestoreSnapshotTier)

instance Core.AWSRequest RestoreSnapshotTier where
  type
    AWSResponse RestoreSnapshotTier =
      RestoreSnapshotTierResponse
  request :: (Service -> Service)
-> RestoreSnapshotTier -> Request RestoreSnapshotTier
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy RestoreSnapshotTier
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RestoreSnapshotTier)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Bool
-> Maybe Int
-> Maybe ISO8601
-> Maybe Text
-> Int
-> RestoreSnapshotTierResponse
RestoreSnapshotTierResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"isPermanentRestore")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"restoreDuration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"restoreStartTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"snapshotId")
            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 RestoreSnapshotTier where
  hashWithSalt :: Int -> RestoreSnapshotTier -> Int
hashWithSalt Int
_salt RestoreSnapshotTier' {Maybe Bool
Maybe Int
Text
snapshotId :: Text
temporaryRestoreDays :: Maybe Int
permanentRestore :: Maybe Bool
dryRun :: Maybe Bool
$sel:snapshotId:RestoreSnapshotTier' :: RestoreSnapshotTier -> Text
$sel:temporaryRestoreDays:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Int
$sel:permanentRestore:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Bool
$sel:dryRun:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
permanentRestore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
temporaryRestoreDays
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
snapshotId

instance Prelude.NFData RestoreSnapshotTier where
  rnf :: RestoreSnapshotTier -> ()
rnf RestoreSnapshotTier' {Maybe Bool
Maybe Int
Text
snapshotId :: Text
temporaryRestoreDays :: Maybe Int
permanentRestore :: Maybe Bool
dryRun :: Maybe Bool
$sel:snapshotId:RestoreSnapshotTier' :: RestoreSnapshotTier -> Text
$sel:temporaryRestoreDays:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Int
$sel:permanentRestore:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Bool
$sel:dryRun:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
permanentRestore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
temporaryRestoreDays
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
snapshotId

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

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

instance Data.ToQuery RestoreSnapshotTier where
  toQuery :: RestoreSnapshotTier -> QueryString
toQuery RestoreSnapshotTier' {Maybe Bool
Maybe Int
Text
snapshotId :: Text
temporaryRestoreDays :: Maybe Int
permanentRestore :: Maybe Bool
dryRun :: Maybe Bool
$sel:snapshotId:RestoreSnapshotTier' :: RestoreSnapshotTier -> Text
$sel:temporaryRestoreDays:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Int
$sel:permanentRestore:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Bool
$sel:dryRun:RestoreSnapshotTier' :: RestoreSnapshotTier -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"RestoreSnapshotTier" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"PermanentRestore" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
permanentRestore,
        ByteString
"TemporaryRestoreDays" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
temporaryRestoreDays,
        ByteString
"SnapshotId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
snapshotId
      ]

-- | /See:/ 'newRestoreSnapshotTierResponse' smart constructor.
data RestoreSnapshotTierResponse = RestoreSnapshotTierResponse'
  { -- | Indicates whether the snapshot is permanently restored. @true@ indicates
    -- a permanent restore. @false@ indicates a temporary restore.
    RestoreSnapshotTierResponse -> Maybe Bool
isPermanentRestore :: Prelude.Maybe Prelude.Bool,
    -- | For temporary restores only. The number of days for which the archived
    -- snapshot is temporarily restored.
    RestoreSnapshotTierResponse -> Maybe Int
restoreDuration :: Prelude.Maybe Prelude.Int,
    -- | The date and time when the snapshot restore process started.
    RestoreSnapshotTierResponse -> Maybe ISO8601
restoreStartTime :: Prelude.Maybe Data.ISO8601,
    -- | The ID of the snapshot.
    RestoreSnapshotTierResponse -> Maybe Text
snapshotId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    RestoreSnapshotTierResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RestoreSnapshotTierResponse -> RestoreSnapshotTierResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreSnapshotTierResponse -> RestoreSnapshotTierResponse -> Bool
$c/= :: RestoreSnapshotTierResponse -> RestoreSnapshotTierResponse -> Bool
== :: RestoreSnapshotTierResponse -> RestoreSnapshotTierResponse -> Bool
$c== :: RestoreSnapshotTierResponse -> RestoreSnapshotTierResponse -> Bool
Prelude.Eq, ReadPrec [RestoreSnapshotTierResponse]
ReadPrec RestoreSnapshotTierResponse
Int -> ReadS RestoreSnapshotTierResponse
ReadS [RestoreSnapshotTierResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestoreSnapshotTierResponse]
$creadListPrec :: ReadPrec [RestoreSnapshotTierResponse]
readPrec :: ReadPrec RestoreSnapshotTierResponse
$creadPrec :: ReadPrec RestoreSnapshotTierResponse
readList :: ReadS [RestoreSnapshotTierResponse]
$creadList :: ReadS [RestoreSnapshotTierResponse]
readsPrec :: Int -> ReadS RestoreSnapshotTierResponse
$creadsPrec :: Int -> ReadS RestoreSnapshotTierResponse
Prelude.Read, Int -> RestoreSnapshotTierResponse -> ShowS
[RestoreSnapshotTierResponse] -> ShowS
RestoreSnapshotTierResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreSnapshotTierResponse] -> ShowS
$cshowList :: [RestoreSnapshotTierResponse] -> ShowS
show :: RestoreSnapshotTierResponse -> String
$cshow :: RestoreSnapshotTierResponse -> String
showsPrec :: Int -> RestoreSnapshotTierResponse -> ShowS
$cshowsPrec :: Int -> RestoreSnapshotTierResponse -> ShowS
Prelude.Show, forall x.
Rep RestoreSnapshotTierResponse x -> RestoreSnapshotTierResponse
forall x.
RestoreSnapshotTierResponse -> Rep RestoreSnapshotTierResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RestoreSnapshotTierResponse x -> RestoreSnapshotTierResponse
$cfrom :: forall x.
RestoreSnapshotTierResponse -> Rep RestoreSnapshotTierResponse x
Prelude.Generic)

-- |
-- Create a value of 'RestoreSnapshotTierResponse' 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:
--
-- 'isPermanentRestore', 'restoreSnapshotTierResponse_isPermanentRestore' - Indicates whether the snapshot is permanently restored. @true@ indicates
-- a permanent restore. @false@ indicates a temporary restore.
--
-- 'restoreDuration', 'restoreSnapshotTierResponse_restoreDuration' - For temporary restores only. The number of days for which the archived
-- snapshot is temporarily restored.
--
-- 'restoreStartTime', 'restoreSnapshotTierResponse_restoreStartTime' - The date and time when the snapshot restore process started.
--
-- 'snapshotId', 'restoreSnapshotTierResponse_snapshotId' - The ID of the snapshot.
--
-- 'httpStatus', 'restoreSnapshotTierResponse_httpStatus' - The response's http status code.
newRestoreSnapshotTierResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RestoreSnapshotTierResponse
newRestoreSnapshotTierResponse :: Int -> RestoreSnapshotTierResponse
newRestoreSnapshotTierResponse Int
pHttpStatus_ =
  RestoreSnapshotTierResponse'
    { $sel:isPermanentRestore:RestoreSnapshotTierResponse' :: Maybe Bool
isPermanentRestore =
        forall a. Maybe a
Prelude.Nothing,
      $sel:restoreDuration:RestoreSnapshotTierResponse' :: Maybe Int
restoreDuration = forall a. Maybe a
Prelude.Nothing,
      $sel:restoreStartTime:RestoreSnapshotTierResponse' :: Maybe ISO8601
restoreStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotId:RestoreSnapshotTierResponse' :: Maybe Text
snapshotId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RestoreSnapshotTierResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Indicates whether the snapshot is permanently restored. @true@ indicates
-- a permanent restore. @false@ indicates a temporary restore.
restoreSnapshotTierResponse_isPermanentRestore :: Lens.Lens' RestoreSnapshotTierResponse (Prelude.Maybe Prelude.Bool)
restoreSnapshotTierResponse_isPermanentRestore :: Lens' RestoreSnapshotTierResponse (Maybe Bool)
restoreSnapshotTierResponse_isPermanentRestore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreSnapshotTierResponse' {Maybe Bool
isPermanentRestore :: Maybe Bool
$sel:isPermanentRestore:RestoreSnapshotTierResponse' :: RestoreSnapshotTierResponse -> Maybe Bool
isPermanentRestore} -> Maybe Bool
isPermanentRestore) (\s :: RestoreSnapshotTierResponse
s@RestoreSnapshotTierResponse' {} Maybe Bool
a -> RestoreSnapshotTierResponse
s {$sel:isPermanentRestore:RestoreSnapshotTierResponse' :: Maybe Bool
isPermanentRestore = Maybe Bool
a} :: RestoreSnapshotTierResponse)

-- | For temporary restores only. The number of days for which the archived
-- snapshot is temporarily restored.
restoreSnapshotTierResponse_restoreDuration :: Lens.Lens' RestoreSnapshotTierResponse (Prelude.Maybe Prelude.Int)
restoreSnapshotTierResponse_restoreDuration :: Lens' RestoreSnapshotTierResponse (Maybe Int)
restoreSnapshotTierResponse_restoreDuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreSnapshotTierResponse' {Maybe Int
restoreDuration :: Maybe Int
$sel:restoreDuration:RestoreSnapshotTierResponse' :: RestoreSnapshotTierResponse -> Maybe Int
restoreDuration} -> Maybe Int
restoreDuration) (\s :: RestoreSnapshotTierResponse
s@RestoreSnapshotTierResponse' {} Maybe Int
a -> RestoreSnapshotTierResponse
s {$sel:restoreDuration:RestoreSnapshotTierResponse' :: Maybe Int
restoreDuration = Maybe Int
a} :: RestoreSnapshotTierResponse)

-- | The date and time when the snapshot restore process started.
restoreSnapshotTierResponse_restoreStartTime :: Lens.Lens' RestoreSnapshotTierResponse (Prelude.Maybe Prelude.UTCTime)
restoreSnapshotTierResponse_restoreStartTime :: Lens' RestoreSnapshotTierResponse (Maybe UTCTime)
restoreSnapshotTierResponse_restoreStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreSnapshotTierResponse' {Maybe ISO8601
restoreStartTime :: Maybe ISO8601
$sel:restoreStartTime:RestoreSnapshotTierResponse' :: RestoreSnapshotTierResponse -> Maybe ISO8601
restoreStartTime} -> Maybe ISO8601
restoreStartTime) (\s :: RestoreSnapshotTierResponse
s@RestoreSnapshotTierResponse' {} Maybe ISO8601
a -> RestoreSnapshotTierResponse
s {$sel:restoreStartTime:RestoreSnapshotTierResponse' :: Maybe ISO8601
restoreStartTime = Maybe ISO8601
a} :: RestoreSnapshotTierResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The ID of the snapshot.
restoreSnapshotTierResponse_snapshotId :: Lens.Lens' RestoreSnapshotTierResponse (Prelude.Maybe Prelude.Text)
restoreSnapshotTierResponse_snapshotId :: Lens' RestoreSnapshotTierResponse (Maybe Text)
restoreSnapshotTierResponse_snapshotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreSnapshotTierResponse' {Maybe Text
snapshotId :: Maybe Text
$sel:snapshotId:RestoreSnapshotTierResponse' :: RestoreSnapshotTierResponse -> Maybe Text
snapshotId} -> Maybe Text
snapshotId) (\s :: RestoreSnapshotTierResponse
s@RestoreSnapshotTierResponse' {} Maybe Text
a -> RestoreSnapshotTierResponse
s {$sel:snapshotId:RestoreSnapshotTierResponse' :: Maybe Text
snapshotId = Maybe Text
a} :: RestoreSnapshotTierResponse)

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

instance Prelude.NFData RestoreSnapshotTierResponse where
  rnf :: RestoreSnapshotTierResponse -> ()
rnf RestoreSnapshotTierResponse' {Int
Maybe Bool
Maybe Int
Maybe Text
Maybe ISO8601
httpStatus :: Int
snapshotId :: Maybe Text
restoreStartTime :: Maybe ISO8601
restoreDuration :: Maybe Int
isPermanentRestore :: Maybe Bool
$sel:httpStatus:RestoreSnapshotTierResponse' :: RestoreSnapshotTierResponse -> Int
$sel:snapshotId:RestoreSnapshotTierResponse' :: RestoreSnapshotTierResponse -> Maybe Text
$sel:restoreStartTime:RestoreSnapshotTierResponse' :: RestoreSnapshotTierResponse -> Maybe ISO8601
$sel:restoreDuration:RestoreSnapshotTierResponse' :: RestoreSnapshotTierResponse -> Maybe Int
$sel:isPermanentRestore:RestoreSnapshotTierResponse' :: RestoreSnapshotTierResponse -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isPermanentRestore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
restoreDuration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
restoreStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
snapshotId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus