{-# 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.EnableFastSnapshotRestores
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enables fast snapshot restores for the specified snapshots in the
-- specified Availability Zones.
--
-- You get the full benefit of fast snapshot restores after they enter the
-- @enabled@ state. To get the current state of fast snapshot restores, use
-- DescribeFastSnapshotRestores. To disable fast snapshot restores, use
-- DisableFastSnapshotRestores.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ebs-fast-snapshot-restore.html Amazon EBS fast snapshot restore>
-- in the /Amazon Elastic Compute Cloud User Guide/.
module Amazonka.EC2.EnableFastSnapshotRestores
  ( -- * Creating a Request
    EnableFastSnapshotRestores (..),
    newEnableFastSnapshotRestores,

    -- * Request Lenses
    enableFastSnapshotRestores_dryRun,
    enableFastSnapshotRestores_availabilityZones,
    enableFastSnapshotRestores_sourceSnapshotIds,

    -- * Destructuring the Response
    EnableFastSnapshotRestoresResponse (..),
    newEnableFastSnapshotRestoresResponse,

    -- * Response Lenses
    enableFastSnapshotRestoresResponse_successful,
    enableFastSnapshotRestoresResponse_unsuccessful,
    enableFastSnapshotRestoresResponse_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:/ 'newEnableFastSnapshotRestores' smart constructor.
data EnableFastSnapshotRestores = EnableFastSnapshotRestores'
  { -- | 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@.
    EnableFastSnapshotRestores -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | One or more Availability Zones. For example, @us-east-2a@.
    EnableFastSnapshotRestores -> [Text]
availabilityZones :: [Prelude.Text],
    -- | The IDs of one or more snapshots. For example, @snap-1234567890abcdef0@.
    -- You can specify a snapshot that was shared with you from another Amazon
    -- Web Services account.
    EnableFastSnapshotRestores -> [Text]
sourceSnapshotIds :: [Prelude.Text]
  }
  deriving (EnableFastSnapshotRestores -> EnableFastSnapshotRestores -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableFastSnapshotRestores -> EnableFastSnapshotRestores -> Bool
$c/= :: EnableFastSnapshotRestores -> EnableFastSnapshotRestores -> Bool
== :: EnableFastSnapshotRestores -> EnableFastSnapshotRestores -> Bool
$c== :: EnableFastSnapshotRestores -> EnableFastSnapshotRestores -> Bool
Prelude.Eq, ReadPrec [EnableFastSnapshotRestores]
ReadPrec EnableFastSnapshotRestores
Int -> ReadS EnableFastSnapshotRestores
ReadS [EnableFastSnapshotRestores]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableFastSnapshotRestores]
$creadListPrec :: ReadPrec [EnableFastSnapshotRestores]
readPrec :: ReadPrec EnableFastSnapshotRestores
$creadPrec :: ReadPrec EnableFastSnapshotRestores
readList :: ReadS [EnableFastSnapshotRestores]
$creadList :: ReadS [EnableFastSnapshotRestores]
readsPrec :: Int -> ReadS EnableFastSnapshotRestores
$creadsPrec :: Int -> ReadS EnableFastSnapshotRestores
Prelude.Read, Int -> EnableFastSnapshotRestores -> ShowS
[EnableFastSnapshotRestores] -> ShowS
EnableFastSnapshotRestores -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableFastSnapshotRestores] -> ShowS
$cshowList :: [EnableFastSnapshotRestores] -> ShowS
show :: EnableFastSnapshotRestores -> String
$cshow :: EnableFastSnapshotRestores -> String
showsPrec :: Int -> EnableFastSnapshotRestores -> ShowS
$cshowsPrec :: Int -> EnableFastSnapshotRestores -> ShowS
Prelude.Show, forall x.
Rep EnableFastSnapshotRestores x -> EnableFastSnapshotRestores
forall x.
EnableFastSnapshotRestores -> Rep EnableFastSnapshotRestores x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EnableFastSnapshotRestores x -> EnableFastSnapshotRestores
$cfrom :: forall x.
EnableFastSnapshotRestores -> Rep EnableFastSnapshotRestores x
Prelude.Generic)

-- |
-- Create a value of 'EnableFastSnapshotRestores' 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', 'enableFastSnapshotRestores_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@.
--
-- 'availabilityZones', 'enableFastSnapshotRestores_availabilityZones' - One or more Availability Zones. For example, @us-east-2a@.
--
-- 'sourceSnapshotIds', 'enableFastSnapshotRestores_sourceSnapshotIds' - The IDs of one or more snapshots. For example, @snap-1234567890abcdef0@.
-- You can specify a snapshot that was shared with you from another Amazon
-- Web Services account.
newEnableFastSnapshotRestores ::
  EnableFastSnapshotRestores
newEnableFastSnapshotRestores :: EnableFastSnapshotRestores
newEnableFastSnapshotRestores =
  EnableFastSnapshotRestores'
    { $sel:dryRun:EnableFastSnapshotRestores' :: Maybe Bool
dryRun =
        forall a. Maybe a
Prelude.Nothing,
      $sel:availabilityZones:EnableFastSnapshotRestores' :: [Text]
availabilityZones = forall a. Monoid a => a
Prelude.mempty,
      $sel:sourceSnapshotIds:EnableFastSnapshotRestores' :: [Text]
sourceSnapshotIds = forall a. Monoid a => a
Prelude.mempty
    }

-- | 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@.
enableFastSnapshotRestores_dryRun :: Lens.Lens' EnableFastSnapshotRestores (Prelude.Maybe Prelude.Bool)
enableFastSnapshotRestores_dryRun :: Lens' EnableFastSnapshotRestores (Maybe Bool)
enableFastSnapshotRestores_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableFastSnapshotRestores' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: EnableFastSnapshotRestores
s@EnableFastSnapshotRestores' {} Maybe Bool
a -> EnableFastSnapshotRestores
s {$sel:dryRun:EnableFastSnapshotRestores' :: Maybe Bool
dryRun = Maybe Bool
a} :: EnableFastSnapshotRestores)

-- | One or more Availability Zones. For example, @us-east-2a@.
enableFastSnapshotRestores_availabilityZones :: Lens.Lens' EnableFastSnapshotRestores [Prelude.Text]
enableFastSnapshotRestores_availabilityZones :: Lens' EnableFastSnapshotRestores [Text]
enableFastSnapshotRestores_availabilityZones = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableFastSnapshotRestores' {[Text]
availabilityZones :: [Text]
$sel:availabilityZones:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> [Text]
availabilityZones} -> [Text]
availabilityZones) (\s :: EnableFastSnapshotRestores
s@EnableFastSnapshotRestores' {} [Text]
a -> EnableFastSnapshotRestores
s {$sel:availabilityZones:EnableFastSnapshotRestores' :: [Text]
availabilityZones = [Text]
a} :: EnableFastSnapshotRestores) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The IDs of one or more snapshots. For example, @snap-1234567890abcdef0@.
-- You can specify a snapshot that was shared with you from another Amazon
-- Web Services account.
enableFastSnapshotRestores_sourceSnapshotIds :: Lens.Lens' EnableFastSnapshotRestores [Prelude.Text]
enableFastSnapshotRestores_sourceSnapshotIds :: Lens' EnableFastSnapshotRestores [Text]
enableFastSnapshotRestores_sourceSnapshotIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableFastSnapshotRestores' {[Text]
sourceSnapshotIds :: [Text]
$sel:sourceSnapshotIds:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> [Text]
sourceSnapshotIds} -> [Text]
sourceSnapshotIds) (\s :: EnableFastSnapshotRestores
s@EnableFastSnapshotRestores' {} [Text]
a -> EnableFastSnapshotRestores
s {$sel:sourceSnapshotIds:EnableFastSnapshotRestores' :: [Text]
sourceSnapshotIds = [Text]
a} :: EnableFastSnapshotRestores) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest EnableFastSnapshotRestores where
  type
    AWSResponse EnableFastSnapshotRestores =
      EnableFastSnapshotRestoresResponse
  request :: (Service -> Service)
-> EnableFastSnapshotRestores -> Request EnableFastSnapshotRestores
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 EnableFastSnapshotRestores
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse EnableFastSnapshotRestores)))
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 [EnableFastSnapshotRestoreSuccessItem]
-> Maybe [EnableFastSnapshotRestoreErrorItem]
-> Int
-> EnableFastSnapshotRestoresResponse
EnableFastSnapshotRestoresResponse'
            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
"successful"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                        )
            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
"unsuccessful"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                        )
            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 EnableFastSnapshotRestores where
  hashWithSalt :: Int -> EnableFastSnapshotRestores -> Int
hashWithSalt Int
_salt EnableFastSnapshotRestores' {[Text]
Maybe Bool
sourceSnapshotIds :: [Text]
availabilityZones :: [Text]
dryRun :: Maybe Bool
$sel:sourceSnapshotIds:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> [Text]
$sel:availabilityZones:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> [Text]
$sel:dryRun:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> 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` [Text]
availabilityZones
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
sourceSnapshotIds

instance Prelude.NFData EnableFastSnapshotRestores where
  rnf :: EnableFastSnapshotRestores -> ()
rnf EnableFastSnapshotRestores' {[Text]
Maybe Bool
sourceSnapshotIds :: [Text]
availabilityZones :: [Text]
dryRun :: Maybe Bool
$sel:sourceSnapshotIds:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> [Text]
$sel:availabilityZones:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> [Text]
$sel:dryRun:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> 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 [Text]
availabilityZones
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
sourceSnapshotIds

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

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

instance Data.ToQuery EnableFastSnapshotRestores where
  toQuery :: EnableFastSnapshotRestores -> QueryString
toQuery EnableFastSnapshotRestores' {[Text]
Maybe Bool
sourceSnapshotIds :: [Text]
availabilityZones :: [Text]
dryRun :: Maybe Bool
$sel:sourceSnapshotIds:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> [Text]
$sel:availabilityZones:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> [Text]
$sel:dryRun:EnableFastSnapshotRestores' :: EnableFastSnapshotRestores -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"EnableFastSnapshotRestores" :: 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,
        forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList
          ByteString
"AvailabilityZone"
          [Text]
availabilityZones,
        forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList
          ByteString
"SourceSnapshotId"
          [Text]
sourceSnapshotIds
      ]

-- | /See:/ 'newEnableFastSnapshotRestoresResponse' smart constructor.
data EnableFastSnapshotRestoresResponse = EnableFastSnapshotRestoresResponse'
  { -- | Information about the snapshots for which fast snapshot restores were
    -- successfully enabled.
    EnableFastSnapshotRestoresResponse
-> Maybe [EnableFastSnapshotRestoreSuccessItem]
successful :: Prelude.Maybe [EnableFastSnapshotRestoreSuccessItem],
    -- | Information about the snapshots for which fast snapshot restores could
    -- not be enabled.
    EnableFastSnapshotRestoresResponse
-> Maybe [EnableFastSnapshotRestoreErrorItem]
unsuccessful :: Prelude.Maybe [EnableFastSnapshotRestoreErrorItem],
    -- | The response's http status code.
    EnableFastSnapshotRestoresResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (EnableFastSnapshotRestoresResponse
-> EnableFastSnapshotRestoresResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableFastSnapshotRestoresResponse
-> EnableFastSnapshotRestoresResponse -> Bool
$c/= :: EnableFastSnapshotRestoresResponse
-> EnableFastSnapshotRestoresResponse -> Bool
== :: EnableFastSnapshotRestoresResponse
-> EnableFastSnapshotRestoresResponse -> Bool
$c== :: EnableFastSnapshotRestoresResponse
-> EnableFastSnapshotRestoresResponse -> Bool
Prelude.Eq, ReadPrec [EnableFastSnapshotRestoresResponse]
ReadPrec EnableFastSnapshotRestoresResponse
Int -> ReadS EnableFastSnapshotRestoresResponse
ReadS [EnableFastSnapshotRestoresResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableFastSnapshotRestoresResponse]
$creadListPrec :: ReadPrec [EnableFastSnapshotRestoresResponse]
readPrec :: ReadPrec EnableFastSnapshotRestoresResponse
$creadPrec :: ReadPrec EnableFastSnapshotRestoresResponse
readList :: ReadS [EnableFastSnapshotRestoresResponse]
$creadList :: ReadS [EnableFastSnapshotRestoresResponse]
readsPrec :: Int -> ReadS EnableFastSnapshotRestoresResponse
$creadsPrec :: Int -> ReadS EnableFastSnapshotRestoresResponse
Prelude.Read, Int -> EnableFastSnapshotRestoresResponse -> ShowS
[EnableFastSnapshotRestoresResponse] -> ShowS
EnableFastSnapshotRestoresResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableFastSnapshotRestoresResponse] -> ShowS
$cshowList :: [EnableFastSnapshotRestoresResponse] -> ShowS
show :: EnableFastSnapshotRestoresResponse -> String
$cshow :: EnableFastSnapshotRestoresResponse -> String
showsPrec :: Int -> EnableFastSnapshotRestoresResponse -> ShowS
$cshowsPrec :: Int -> EnableFastSnapshotRestoresResponse -> ShowS
Prelude.Show, forall x.
Rep EnableFastSnapshotRestoresResponse x
-> EnableFastSnapshotRestoresResponse
forall x.
EnableFastSnapshotRestoresResponse
-> Rep EnableFastSnapshotRestoresResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EnableFastSnapshotRestoresResponse x
-> EnableFastSnapshotRestoresResponse
$cfrom :: forall x.
EnableFastSnapshotRestoresResponse
-> Rep EnableFastSnapshotRestoresResponse x
Prelude.Generic)

-- |
-- Create a value of 'EnableFastSnapshotRestoresResponse' 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:
--
-- 'successful', 'enableFastSnapshotRestoresResponse_successful' - Information about the snapshots for which fast snapshot restores were
-- successfully enabled.
--
-- 'unsuccessful', 'enableFastSnapshotRestoresResponse_unsuccessful' - Information about the snapshots for which fast snapshot restores could
-- not be enabled.
--
-- 'httpStatus', 'enableFastSnapshotRestoresResponse_httpStatus' - The response's http status code.
newEnableFastSnapshotRestoresResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  EnableFastSnapshotRestoresResponse
newEnableFastSnapshotRestoresResponse :: Int -> EnableFastSnapshotRestoresResponse
newEnableFastSnapshotRestoresResponse Int
pHttpStatus_ =
  EnableFastSnapshotRestoresResponse'
    { $sel:successful:EnableFastSnapshotRestoresResponse' :: Maybe [EnableFastSnapshotRestoreSuccessItem]
successful =
        forall a. Maybe a
Prelude.Nothing,
      $sel:unsuccessful:EnableFastSnapshotRestoresResponse' :: Maybe [EnableFastSnapshotRestoreErrorItem]
unsuccessful = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:EnableFastSnapshotRestoresResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the snapshots for which fast snapshot restores were
-- successfully enabled.
enableFastSnapshotRestoresResponse_successful :: Lens.Lens' EnableFastSnapshotRestoresResponse (Prelude.Maybe [EnableFastSnapshotRestoreSuccessItem])
enableFastSnapshotRestoresResponse_successful :: Lens'
  EnableFastSnapshotRestoresResponse
  (Maybe [EnableFastSnapshotRestoreSuccessItem])
enableFastSnapshotRestoresResponse_successful = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableFastSnapshotRestoresResponse' {Maybe [EnableFastSnapshotRestoreSuccessItem]
successful :: Maybe [EnableFastSnapshotRestoreSuccessItem]
$sel:successful:EnableFastSnapshotRestoresResponse' :: EnableFastSnapshotRestoresResponse
-> Maybe [EnableFastSnapshotRestoreSuccessItem]
successful} -> Maybe [EnableFastSnapshotRestoreSuccessItem]
successful) (\s :: EnableFastSnapshotRestoresResponse
s@EnableFastSnapshotRestoresResponse' {} Maybe [EnableFastSnapshotRestoreSuccessItem]
a -> EnableFastSnapshotRestoresResponse
s {$sel:successful:EnableFastSnapshotRestoresResponse' :: Maybe [EnableFastSnapshotRestoreSuccessItem]
successful = Maybe [EnableFastSnapshotRestoreSuccessItem]
a} :: EnableFastSnapshotRestoresResponse) 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

-- | Information about the snapshots for which fast snapshot restores could
-- not be enabled.
enableFastSnapshotRestoresResponse_unsuccessful :: Lens.Lens' EnableFastSnapshotRestoresResponse (Prelude.Maybe [EnableFastSnapshotRestoreErrorItem])
enableFastSnapshotRestoresResponse_unsuccessful :: Lens'
  EnableFastSnapshotRestoresResponse
  (Maybe [EnableFastSnapshotRestoreErrorItem])
enableFastSnapshotRestoresResponse_unsuccessful = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableFastSnapshotRestoresResponse' {Maybe [EnableFastSnapshotRestoreErrorItem]
unsuccessful :: Maybe [EnableFastSnapshotRestoreErrorItem]
$sel:unsuccessful:EnableFastSnapshotRestoresResponse' :: EnableFastSnapshotRestoresResponse
-> Maybe [EnableFastSnapshotRestoreErrorItem]
unsuccessful} -> Maybe [EnableFastSnapshotRestoreErrorItem]
unsuccessful) (\s :: EnableFastSnapshotRestoresResponse
s@EnableFastSnapshotRestoresResponse' {} Maybe [EnableFastSnapshotRestoreErrorItem]
a -> EnableFastSnapshotRestoresResponse
s {$sel:unsuccessful:EnableFastSnapshotRestoresResponse' :: Maybe [EnableFastSnapshotRestoreErrorItem]
unsuccessful = Maybe [EnableFastSnapshotRestoreErrorItem]
a} :: EnableFastSnapshotRestoresResponse) 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

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

instance
  Prelude.NFData
    EnableFastSnapshotRestoresResponse
  where
  rnf :: EnableFastSnapshotRestoresResponse -> ()
rnf EnableFastSnapshotRestoresResponse' {Int
Maybe [EnableFastSnapshotRestoreErrorItem]
Maybe [EnableFastSnapshotRestoreSuccessItem]
httpStatus :: Int
unsuccessful :: Maybe [EnableFastSnapshotRestoreErrorItem]
successful :: Maybe [EnableFastSnapshotRestoreSuccessItem]
$sel:httpStatus:EnableFastSnapshotRestoresResponse' :: EnableFastSnapshotRestoresResponse -> Int
$sel:unsuccessful:EnableFastSnapshotRestoresResponse' :: EnableFastSnapshotRestoresResponse
-> Maybe [EnableFastSnapshotRestoreErrorItem]
$sel:successful:EnableFastSnapshotRestoresResponse' :: EnableFastSnapshotRestoresResponse
-> Maybe [EnableFastSnapshotRestoreSuccessItem]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [EnableFastSnapshotRestoreSuccessItem]
successful
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [EnableFastSnapshotRestoreErrorItem]
unsuccessful
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus