{-# 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 #-}
module Amazonka.EC2.DescribeFastSnapshotRestores
(
DescribeFastSnapshotRestores (..),
newDescribeFastSnapshotRestores,
describeFastSnapshotRestores_dryRun,
describeFastSnapshotRestores_filters,
describeFastSnapshotRestores_maxResults,
describeFastSnapshotRestores_nextToken,
DescribeFastSnapshotRestoresResponse (..),
newDescribeFastSnapshotRestoresResponse,
describeFastSnapshotRestoresResponse_fastSnapshotRestores,
describeFastSnapshotRestoresResponse_nextToken,
describeFastSnapshotRestoresResponse_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
data DescribeFastSnapshotRestores = DescribeFastSnapshotRestores'
{
DescribeFastSnapshotRestores -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
DescribeFastSnapshotRestores -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
DescribeFastSnapshotRestores -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
DescribeFastSnapshotRestores -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
}
deriving (DescribeFastSnapshotRestores
-> DescribeFastSnapshotRestores -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFastSnapshotRestores
-> DescribeFastSnapshotRestores -> Bool
$c/= :: DescribeFastSnapshotRestores
-> DescribeFastSnapshotRestores -> Bool
== :: DescribeFastSnapshotRestores
-> DescribeFastSnapshotRestores -> Bool
$c== :: DescribeFastSnapshotRestores
-> DescribeFastSnapshotRestores -> Bool
Prelude.Eq, ReadPrec [DescribeFastSnapshotRestores]
ReadPrec DescribeFastSnapshotRestores
Int -> ReadS DescribeFastSnapshotRestores
ReadS [DescribeFastSnapshotRestores]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFastSnapshotRestores]
$creadListPrec :: ReadPrec [DescribeFastSnapshotRestores]
readPrec :: ReadPrec DescribeFastSnapshotRestores
$creadPrec :: ReadPrec DescribeFastSnapshotRestores
readList :: ReadS [DescribeFastSnapshotRestores]
$creadList :: ReadS [DescribeFastSnapshotRestores]
readsPrec :: Int -> ReadS DescribeFastSnapshotRestores
$creadsPrec :: Int -> ReadS DescribeFastSnapshotRestores
Prelude.Read, Int -> DescribeFastSnapshotRestores -> ShowS
[DescribeFastSnapshotRestores] -> ShowS
DescribeFastSnapshotRestores -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFastSnapshotRestores] -> ShowS
$cshowList :: [DescribeFastSnapshotRestores] -> ShowS
show :: DescribeFastSnapshotRestores -> String
$cshow :: DescribeFastSnapshotRestores -> String
showsPrec :: Int -> DescribeFastSnapshotRestores -> ShowS
$cshowsPrec :: Int -> DescribeFastSnapshotRestores -> ShowS
Prelude.Show, forall x.
Rep DescribeFastSnapshotRestores x -> DescribeFastSnapshotRestores
forall x.
DescribeFastSnapshotRestores -> Rep DescribeFastSnapshotRestores x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeFastSnapshotRestores x -> DescribeFastSnapshotRestores
$cfrom :: forall x.
DescribeFastSnapshotRestores -> Rep DescribeFastSnapshotRestores x
Prelude.Generic)
newDescribeFastSnapshotRestores ::
DescribeFastSnapshotRestores
newDescribeFastSnapshotRestores :: DescribeFastSnapshotRestores
newDescribeFastSnapshotRestores =
DescribeFastSnapshotRestores'
{ $sel:dryRun:DescribeFastSnapshotRestores' :: Maybe Bool
dryRun =
forall a. Maybe a
Prelude.Nothing,
$sel:filters:DescribeFastSnapshotRestores' :: Maybe [Filter]
filters = forall a. Maybe a
Prelude.Nothing,
$sel:maxResults:DescribeFastSnapshotRestores' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:DescribeFastSnapshotRestores' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
}
describeFastSnapshotRestores_dryRun :: Lens.Lens' DescribeFastSnapshotRestores (Prelude.Maybe Prelude.Bool)
describeFastSnapshotRestores_dryRun :: Lens' DescribeFastSnapshotRestores (Maybe Bool)
describeFastSnapshotRestores_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFastSnapshotRestores' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DescribeFastSnapshotRestores
s@DescribeFastSnapshotRestores' {} Maybe Bool
a -> DescribeFastSnapshotRestores
s {$sel:dryRun:DescribeFastSnapshotRestores' :: Maybe Bool
dryRun = Maybe Bool
a} :: DescribeFastSnapshotRestores)
describeFastSnapshotRestores_filters :: Lens.Lens' DescribeFastSnapshotRestores (Prelude.Maybe [Filter])
describeFastSnapshotRestores_filters :: Lens' DescribeFastSnapshotRestores (Maybe [Filter])
describeFastSnapshotRestores_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFastSnapshotRestores' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: DescribeFastSnapshotRestores
s@DescribeFastSnapshotRestores' {} Maybe [Filter]
a -> DescribeFastSnapshotRestores
s {$sel:filters:DescribeFastSnapshotRestores' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: DescribeFastSnapshotRestores) 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
describeFastSnapshotRestores_maxResults :: Lens.Lens' DescribeFastSnapshotRestores (Prelude.Maybe Prelude.Natural)
describeFastSnapshotRestores_maxResults :: Lens' DescribeFastSnapshotRestores (Maybe Natural)
describeFastSnapshotRestores_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFastSnapshotRestores' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: DescribeFastSnapshotRestores
s@DescribeFastSnapshotRestores' {} Maybe Natural
a -> DescribeFastSnapshotRestores
s {$sel:maxResults:DescribeFastSnapshotRestores' :: Maybe Natural
maxResults = Maybe Natural
a} :: DescribeFastSnapshotRestores)
describeFastSnapshotRestores_nextToken :: Lens.Lens' DescribeFastSnapshotRestores (Prelude.Maybe Prelude.Text)
describeFastSnapshotRestores_nextToken :: Lens' DescribeFastSnapshotRestores (Maybe Text)
describeFastSnapshotRestores_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFastSnapshotRestores' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeFastSnapshotRestores
s@DescribeFastSnapshotRestores' {} Maybe Text
a -> DescribeFastSnapshotRestores
s {$sel:nextToken:DescribeFastSnapshotRestores' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeFastSnapshotRestores)
instance Core.AWSPager DescribeFastSnapshotRestores where
page :: DescribeFastSnapshotRestores
-> AWSResponse DescribeFastSnapshotRestores
-> Maybe DescribeFastSnapshotRestores
page DescribeFastSnapshotRestores
rq AWSResponse DescribeFastSnapshotRestores
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse DescribeFastSnapshotRestores
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeFastSnapshotRestoresResponse (Maybe Text)
describeFastSnapshotRestoresResponse_nextToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
) =
forall a. Maybe a
Prelude.Nothing
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse DescribeFastSnapshotRestores
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
DescribeFastSnapshotRestoresResponse
(Maybe [DescribeFastSnapshotRestoreSuccessItem])
describeFastSnapshotRestoresResponse_fastSnapshotRestores
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
) =
forall a. Maybe a
Prelude.Nothing
| Bool
Prelude.otherwise =
forall a. a -> Maybe a
Prelude.Just
forall a b. (a -> b) -> a -> b
Prelude.$ DescribeFastSnapshotRestores
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeFastSnapshotRestores (Maybe Text)
describeFastSnapshotRestores_nextToken
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeFastSnapshotRestores
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeFastSnapshotRestoresResponse (Maybe Text)
describeFastSnapshotRestoresResponse_nextToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
instance Core.AWSRequest DescribeFastSnapshotRestores where
type
AWSResponse DescribeFastSnapshotRestores =
DescribeFastSnapshotRestoresResponse
request :: (Service -> Service)
-> DescribeFastSnapshotRestores
-> Request DescribeFastSnapshotRestores
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 DescribeFastSnapshotRestores
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse DescribeFastSnapshotRestores)))
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 [DescribeFastSnapshotRestoreSuccessItem]
-> Maybe Text -> Int -> DescribeFastSnapshotRestoresResponse
DescribeFastSnapshotRestoresResponse'
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
"fastSnapshotRestoreSet"
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
"nextToken")
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
DescribeFastSnapshotRestores
where
hashWithSalt :: Int -> DescribeFastSnapshotRestores -> Int
hashWithSalt Int
_salt DescribeFastSnapshotRestores' {Maybe Bool
Maybe Natural
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:nextToken:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe Text
$sel:maxResults:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe Natural
$sel:filters:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe [Filter]
$sel:dryRun:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> 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 [Filter]
filters
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
instance Prelude.NFData DescribeFastSnapshotRestores where
rnf :: DescribeFastSnapshotRestores -> ()
rnf DescribeFastSnapshotRestores' {Maybe Bool
Maybe Natural
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:nextToken:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe Text
$sel:maxResults:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe Natural
$sel:filters:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe [Filter]
$sel:dryRun:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> 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 [Filter]
filters
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
instance Data.ToHeaders DescribeFastSnapshotRestores where
toHeaders :: DescribeFastSnapshotRestores -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath DescribeFastSnapshotRestores where
toPath :: DescribeFastSnapshotRestores -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DescribeFastSnapshotRestores where
toQuery :: DescribeFastSnapshotRestores -> QueryString
toQuery DescribeFastSnapshotRestores' {Maybe Bool
Maybe Natural
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:nextToken:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe Text
$sel:maxResults:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe Natural
$sel:filters:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe [Filter]
$sel:dryRun:DescribeFastSnapshotRestores' :: DescribeFastSnapshotRestores -> Maybe Bool
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"Action"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DescribeFastSnapshotRestores" ::
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. ToQuery a => a -> QueryString
Data.toQuery
(forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Filter" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Filter]
filters),
ByteString
"MaxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
]
data DescribeFastSnapshotRestoresResponse = DescribeFastSnapshotRestoresResponse'
{
DescribeFastSnapshotRestoresResponse
-> Maybe [DescribeFastSnapshotRestoreSuccessItem]
fastSnapshotRestores :: Prelude.Maybe [DescribeFastSnapshotRestoreSuccessItem],
DescribeFastSnapshotRestoresResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
DescribeFastSnapshotRestoresResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DescribeFastSnapshotRestoresResponse
-> DescribeFastSnapshotRestoresResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFastSnapshotRestoresResponse
-> DescribeFastSnapshotRestoresResponse -> Bool
$c/= :: DescribeFastSnapshotRestoresResponse
-> DescribeFastSnapshotRestoresResponse -> Bool
== :: DescribeFastSnapshotRestoresResponse
-> DescribeFastSnapshotRestoresResponse -> Bool
$c== :: DescribeFastSnapshotRestoresResponse
-> DescribeFastSnapshotRestoresResponse -> Bool
Prelude.Eq, ReadPrec [DescribeFastSnapshotRestoresResponse]
ReadPrec DescribeFastSnapshotRestoresResponse
Int -> ReadS DescribeFastSnapshotRestoresResponse
ReadS [DescribeFastSnapshotRestoresResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFastSnapshotRestoresResponse]
$creadListPrec :: ReadPrec [DescribeFastSnapshotRestoresResponse]
readPrec :: ReadPrec DescribeFastSnapshotRestoresResponse
$creadPrec :: ReadPrec DescribeFastSnapshotRestoresResponse
readList :: ReadS [DescribeFastSnapshotRestoresResponse]
$creadList :: ReadS [DescribeFastSnapshotRestoresResponse]
readsPrec :: Int -> ReadS DescribeFastSnapshotRestoresResponse
$creadsPrec :: Int -> ReadS DescribeFastSnapshotRestoresResponse
Prelude.Read, Int -> DescribeFastSnapshotRestoresResponse -> ShowS
[DescribeFastSnapshotRestoresResponse] -> ShowS
DescribeFastSnapshotRestoresResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFastSnapshotRestoresResponse] -> ShowS
$cshowList :: [DescribeFastSnapshotRestoresResponse] -> ShowS
show :: DescribeFastSnapshotRestoresResponse -> String
$cshow :: DescribeFastSnapshotRestoresResponse -> String
showsPrec :: Int -> DescribeFastSnapshotRestoresResponse -> ShowS
$cshowsPrec :: Int -> DescribeFastSnapshotRestoresResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeFastSnapshotRestoresResponse x
-> DescribeFastSnapshotRestoresResponse
forall x.
DescribeFastSnapshotRestoresResponse
-> Rep DescribeFastSnapshotRestoresResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeFastSnapshotRestoresResponse x
-> DescribeFastSnapshotRestoresResponse
$cfrom :: forall x.
DescribeFastSnapshotRestoresResponse
-> Rep DescribeFastSnapshotRestoresResponse x
Prelude.Generic)
newDescribeFastSnapshotRestoresResponse ::
Prelude.Int ->
DescribeFastSnapshotRestoresResponse
newDescribeFastSnapshotRestoresResponse :: Int -> DescribeFastSnapshotRestoresResponse
newDescribeFastSnapshotRestoresResponse Int
pHttpStatus_ =
DescribeFastSnapshotRestoresResponse'
{ $sel:fastSnapshotRestores:DescribeFastSnapshotRestoresResponse' :: Maybe [DescribeFastSnapshotRestoreSuccessItem]
fastSnapshotRestores =
forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:DescribeFastSnapshotRestoresResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:DescribeFastSnapshotRestoresResponse' :: Int
httpStatus = Int
pHttpStatus_
}
describeFastSnapshotRestoresResponse_fastSnapshotRestores :: Lens.Lens' DescribeFastSnapshotRestoresResponse (Prelude.Maybe [DescribeFastSnapshotRestoreSuccessItem])
describeFastSnapshotRestoresResponse_fastSnapshotRestores :: Lens'
DescribeFastSnapshotRestoresResponse
(Maybe [DescribeFastSnapshotRestoreSuccessItem])
describeFastSnapshotRestoresResponse_fastSnapshotRestores = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFastSnapshotRestoresResponse' {Maybe [DescribeFastSnapshotRestoreSuccessItem]
fastSnapshotRestores :: Maybe [DescribeFastSnapshotRestoreSuccessItem]
$sel:fastSnapshotRestores:DescribeFastSnapshotRestoresResponse' :: DescribeFastSnapshotRestoresResponse
-> Maybe [DescribeFastSnapshotRestoreSuccessItem]
fastSnapshotRestores} -> Maybe [DescribeFastSnapshotRestoreSuccessItem]
fastSnapshotRestores) (\s :: DescribeFastSnapshotRestoresResponse
s@DescribeFastSnapshotRestoresResponse' {} Maybe [DescribeFastSnapshotRestoreSuccessItem]
a -> DescribeFastSnapshotRestoresResponse
s {$sel:fastSnapshotRestores:DescribeFastSnapshotRestoresResponse' :: Maybe [DescribeFastSnapshotRestoreSuccessItem]
fastSnapshotRestores = Maybe [DescribeFastSnapshotRestoreSuccessItem]
a} :: DescribeFastSnapshotRestoresResponse) 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
describeFastSnapshotRestoresResponse_nextToken :: Lens.Lens' DescribeFastSnapshotRestoresResponse (Prelude.Maybe Prelude.Text)
describeFastSnapshotRestoresResponse_nextToken :: Lens' DescribeFastSnapshotRestoresResponse (Maybe Text)
describeFastSnapshotRestoresResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFastSnapshotRestoresResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeFastSnapshotRestoresResponse' :: DescribeFastSnapshotRestoresResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeFastSnapshotRestoresResponse
s@DescribeFastSnapshotRestoresResponse' {} Maybe Text
a -> DescribeFastSnapshotRestoresResponse
s {$sel:nextToken:DescribeFastSnapshotRestoresResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeFastSnapshotRestoresResponse)
describeFastSnapshotRestoresResponse_httpStatus :: Lens.Lens' DescribeFastSnapshotRestoresResponse Prelude.Int
describeFastSnapshotRestoresResponse_httpStatus :: Lens' DescribeFastSnapshotRestoresResponse Int
describeFastSnapshotRestoresResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFastSnapshotRestoresResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeFastSnapshotRestoresResponse' :: DescribeFastSnapshotRestoresResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeFastSnapshotRestoresResponse
s@DescribeFastSnapshotRestoresResponse' {} Int
a -> DescribeFastSnapshotRestoresResponse
s {$sel:httpStatus:DescribeFastSnapshotRestoresResponse' :: Int
httpStatus = Int
a} :: DescribeFastSnapshotRestoresResponse)
instance
Prelude.NFData
DescribeFastSnapshotRestoresResponse
where
rnf :: DescribeFastSnapshotRestoresResponse -> ()
rnf DescribeFastSnapshotRestoresResponse' {Int
Maybe [DescribeFastSnapshotRestoreSuccessItem]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
fastSnapshotRestores :: Maybe [DescribeFastSnapshotRestoreSuccessItem]
$sel:httpStatus:DescribeFastSnapshotRestoresResponse' :: DescribeFastSnapshotRestoresResponse -> Int
$sel:nextToken:DescribeFastSnapshotRestoresResponse' :: DescribeFastSnapshotRestoresResponse -> Maybe Text
$sel:fastSnapshotRestores:DescribeFastSnapshotRestoresResponse' :: DescribeFastSnapshotRestoresResponse
-> Maybe [DescribeFastSnapshotRestoreSuccessItem]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [DescribeFastSnapshotRestoreSuccessItem]
fastSnapshotRestores
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus