{-# 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.FSx.DescribeSnapshots
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the description of specific Amazon FSx for OpenZFS snapshots, if
-- a @SnapshotIds@ value is provided. Otherwise, this operation returns all
-- snapshots owned by your Amazon Web Services account in the Amazon Web
-- Services Region of the endpoint that you\'re calling.
--
-- When retrieving all snapshots, you can optionally specify the
-- @MaxResults@ parameter to limit the number of snapshots in a response.
-- If more backups remain, Amazon FSx returns a @NextToken@ value in the
-- response. In this case, send a later request with the @NextToken@
-- request parameter set to the value of @NextToken@ from the last
-- response.
--
-- Use this operation in an iterative process to retrieve a list of your
-- snapshots. @DescribeSnapshots@ is called first without a @NextToken@
-- value. Then the operation continues to be called with the @NextToken@
-- parameter set to the value of the last @NextToken@ value until a
-- response has no @NextToken@ value.
--
-- When using this operation, keep the following in mind:
--
-- -   The operation might return fewer than the @MaxResults@ value of
--     snapshot descriptions while still including a @NextToken@ value.
--
-- -   The order of snapshots returned in the response of one
--     @DescribeSnapshots@ call and the order of backups returned across
--     the responses of a multi-call iteration is unspecified.
module Amazonka.FSx.DescribeSnapshots
  ( -- * Creating a Request
    DescribeSnapshots (..),
    newDescribeSnapshots,

    -- * Request Lenses
    describeSnapshots_filters,
    describeSnapshots_maxResults,
    describeSnapshots_nextToken,
    describeSnapshots_snapshotIds,

    -- * Destructuring the Response
    DescribeSnapshotsResponse (..),
    newDescribeSnapshotsResponse,

    -- * Response Lenses
    describeSnapshotsResponse_nextToken,
    describeSnapshotsResponse_snapshots,
    describeSnapshotsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeSnapshots' smart constructor.
data DescribeSnapshots = DescribeSnapshots'
  { -- | The filters structure. The supported names are @file-system-id@ or
    -- @volume-id@.
    DescribeSnapshots -> Maybe [SnapshotFilter]
filters :: Prelude.Maybe [SnapshotFilter],
    DescribeSnapshots -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    DescribeSnapshots -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The IDs of the snapshots that you want to retrieve. This parameter value
    -- overrides any filters. If any IDs aren\'t found, a @SnapshotNotFound@
    -- error occurs.
    DescribeSnapshots -> Maybe [Text]
snapshotIds :: Prelude.Maybe [Prelude.Text]
  }
  deriving (DescribeSnapshots -> DescribeSnapshots -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSnapshots -> DescribeSnapshots -> Bool
$c/= :: DescribeSnapshots -> DescribeSnapshots -> Bool
== :: DescribeSnapshots -> DescribeSnapshots -> Bool
$c== :: DescribeSnapshots -> DescribeSnapshots -> Bool
Prelude.Eq, ReadPrec [DescribeSnapshots]
ReadPrec DescribeSnapshots
Int -> ReadS DescribeSnapshots
ReadS [DescribeSnapshots]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSnapshots]
$creadListPrec :: ReadPrec [DescribeSnapshots]
readPrec :: ReadPrec DescribeSnapshots
$creadPrec :: ReadPrec DescribeSnapshots
readList :: ReadS [DescribeSnapshots]
$creadList :: ReadS [DescribeSnapshots]
readsPrec :: Int -> ReadS DescribeSnapshots
$creadsPrec :: Int -> ReadS DescribeSnapshots
Prelude.Read, Int -> DescribeSnapshots -> ShowS
[DescribeSnapshots] -> ShowS
DescribeSnapshots -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSnapshots] -> ShowS
$cshowList :: [DescribeSnapshots] -> ShowS
show :: DescribeSnapshots -> String
$cshow :: DescribeSnapshots -> String
showsPrec :: Int -> DescribeSnapshots -> ShowS
$cshowsPrec :: Int -> DescribeSnapshots -> ShowS
Prelude.Show, forall x. Rep DescribeSnapshots x -> DescribeSnapshots
forall x. DescribeSnapshots -> Rep DescribeSnapshots x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeSnapshots x -> DescribeSnapshots
$cfrom :: forall x. DescribeSnapshots -> Rep DescribeSnapshots x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSnapshots' 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:
--
-- 'filters', 'describeSnapshots_filters' - The filters structure. The supported names are @file-system-id@ or
-- @volume-id@.
--
-- 'maxResults', 'describeSnapshots_maxResults' - Undocumented member.
--
-- 'nextToken', 'describeSnapshots_nextToken' - Undocumented member.
--
-- 'snapshotIds', 'describeSnapshots_snapshotIds' - The IDs of the snapshots that you want to retrieve. This parameter value
-- overrides any filters. If any IDs aren\'t found, a @SnapshotNotFound@
-- error occurs.
newDescribeSnapshots ::
  DescribeSnapshots
newDescribeSnapshots :: DescribeSnapshots
newDescribeSnapshots =
  DescribeSnapshots'
    { $sel:filters:DescribeSnapshots' :: Maybe [SnapshotFilter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:DescribeSnapshots' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeSnapshots' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotIds:DescribeSnapshots' :: Maybe [Text]
snapshotIds = forall a. Maybe a
Prelude.Nothing
    }

-- | The filters structure. The supported names are @file-system-id@ or
-- @volume-id@.
describeSnapshots_filters :: Lens.Lens' DescribeSnapshots (Prelude.Maybe [SnapshotFilter])
describeSnapshots_filters :: Lens' DescribeSnapshots (Maybe [SnapshotFilter])
describeSnapshots_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshots' {Maybe [SnapshotFilter]
filters :: Maybe [SnapshotFilter]
$sel:filters:DescribeSnapshots' :: DescribeSnapshots -> Maybe [SnapshotFilter]
filters} -> Maybe [SnapshotFilter]
filters) (\s :: DescribeSnapshots
s@DescribeSnapshots' {} Maybe [SnapshotFilter]
a -> DescribeSnapshots
s {$sel:filters:DescribeSnapshots' :: Maybe [SnapshotFilter]
filters = Maybe [SnapshotFilter]
a} :: DescribeSnapshots) 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

-- | Undocumented member.
describeSnapshots_maxResults :: Lens.Lens' DescribeSnapshots (Prelude.Maybe Prelude.Natural)
describeSnapshots_maxResults :: Lens' DescribeSnapshots (Maybe Natural)
describeSnapshots_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshots' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:DescribeSnapshots' :: DescribeSnapshots -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: DescribeSnapshots
s@DescribeSnapshots' {} Maybe Natural
a -> DescribeSnapshots
s {$sel:maxResults:DescribeSnapshots' :: Maybe Natural
maxResults = Maybe Natural
a} :: DescribeSnapshots)

-- | Undocumented member.
describeSnapshots_nextToken :: Lens.Lens' DescribeSnapshots (Prelude.Maybe Prelude.Text)
describeSnapshots_nextToken :: Lens' DescribeSnapshots (Maybe Text)
describeSnapshots_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshots' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeSnapshots' :: DescribeSnapshots -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeSnapshots
s@DescribeSnapshots' {} Maybe Text
a -> DescribeSnapshots
s {$sel:nextToken:DescribeSnapshots' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeSnapshots)

-- | The IDs of the snapshots that you want to retrieve. This parameter value
-- overrides any filters. If any IDs aren\'t found, a @SnapshotNotFound@
-- error occurs.
describeSnapshots_snapshotIds :: Lens.Lens' DescribeSnapshots (Prelude.Maybe [Prelude.Text])
describeSnapshots_snapshotIds :: Lens' DescribeSnapshots (Maybe [Text])
describeSnapshots_snapshotIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshots' {Maybe [Text]
snapshotIds :: Maybe [Text]
$sel:snapshotIds:DescribeSnapshots' :: DescribeSnapshots -> Maybe [Text]
snapshotIds} -> Maybe [Text]
snapshotIds) (\s :: DescribeSnapshots
s@DescribeSnapshots' {} Maybe [Text]
a -> DescribeSnapshots
s {$sel:snapshotIds:DescribeSnapshots' :: Maybe [Text]
snapshotIds = Maybe [Text]
a} :: DescribeSnapshots) 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

instance Core.AWSRequest DescribeSnapshots where
  type
    AWSResponse DescribeSnapshots =
      DescribeSnapshotsResponse
  request :: (Service -> Service)
-> DescribeSnapshots -> Request DescribeSnapshots
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 DescribeSnapshots
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeSnapshots)))
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 -> Maybe [Snapshot] -> Int -> DescribeSnapshotsResponse
DescribeSnapshotsResponse'
            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
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Snapshots" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 DescribeSnapshots where
  hashWithSalt :: Int -> DescribeSnapshots -> Int
hashWithSalt Int
_salt DescribeSnapshots' {Maybe Natural
Maybe [Text]
Maybe [SnapshotFilter]
Maybe Text
snapshotIds :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [SnapshotFilter]
$sel:snapshotIds:DescribeSnapshots' :: DescribeSnapshots -> Maybe [Text]
$sel:nextToken:DescribeSnapshots' :: DescribeSnapshots -> Maybe Text
$sel:maxResults:DescribeSnapshots' :: DescribeSnapshots -> Maybe Natural
$sel:filters:DescribeSnapshots' :: DescribeSnapshots -> Maybe [SnapshotFilter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SnapshotFilter]
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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
snapshotIds

instance Prelude.NFData DescribeSnapshots where
  rnf :: DescribeSnapshots -> ()
rnf DescribeSnapshots' {Maybe Natural
Maybe [Text]
Maybe [SnapshotFilter]
Maybe Text
snapshotIds :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [SnapshotFilter]
$sel:snapshotIds:DescribeSnapshots' :: DescribeSnapshots -> Maybe [Text]
$sel:nextToken:DescribeSnapshots' :: DescribeSnapshots -> Maybe Text
$sel:maxResults:DescribeSnapshots' :: DescribeSnapshots -> Maybe Natural
$sel:filters:DescribeSnapshots' :: DescribeSnapshots -> Maybe [SnapshotFilter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [SnapshotFilter]
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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
snapshotIds

instance Data.ToHeaders DescribeSnapshots where
  toHeaders :: DescribeSnapshots -> 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
"AWSSimbaAPIService_v20180301.DescribeSnapshots" ::
                          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 DescribeSnapshots where
  toJSON :: DescribeSnapshots -> Value
toJSON DescribeSnapshots' {Maybe Natural
Maybe [Text]
Maybe [SnapshotFilter]
Maybe Text
snapshotIds :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [SnapshotFilter]
$sel:snapshotIds:DescribeSnapshots' :: DescribeSnapshots -> Maybe [Text]
$sel:nextToken:DescribeSnapshots' :: DescribeSnapshots -> Maybe Text
$sel:maxResults:DescribeSnapshots' :: DescribeSnapshots -> Maybe Natural
$sel:filters:DescribeSnapshots' :: DescribeSnapshots -> Maybe [SnapshotFilter]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SnapshotFilter]
filters,
            (Key
"MaxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            (Key
"SnapshotIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
snapshotIds
          ]
      )

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

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

-- | /See:/ 'newDescribeSnapshotsResponse' smart constructor.
data DescribeSnapshotsResponse = DescribeSnapshotsResponse'
  { DescribeSnapshotsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of snapshots.
    DescribeSnapshotsResponse -> Maybe [Snapshot]
snapshots :: Prelude.Maybe [Snapshot],
    -- | The response's http status code.
    DescribeSnapshotsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeSnapshotsResponse -> DescribeSnapshotsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSnapshotsResponse -> DescribeSnapshotsResponse -> Bool
$c/= :: DescribeSnapshotsResponse -> DescribeSnapshotsResponse -> Bool
== :: DescribeSnapshotsResponse -> DescribeSnapshotsResponse -> Bool
$c== :: DescribeSnapshotsResponse -> DescribeSnapshotsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeSnapshotsResponse]
ReadPrec DescribeSnapshotsResponse
Int -> ReadS DescribeSnapshotsResponse
ReadS [DescribeSnapshotsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSnapshotsResponse]
$creadListPrec :: ReadPrec [DescribeSnapshotsResponse]
readPrec :: ReadPrec DescribeSnapshotsResponse
$creadPrec :: ReadPrec DescribeSnapshotsResponse
readList :: ReadS [DescribeSnapshotsResponse]
$creadList :: ReadS [DescribeSnapshotsResponse]
readsPrec :: Int -> ReadS DescribeSnapshotsResponse
$creadsPrec :: Int -> ReadS DescribeSnapshotsResponse
Prelude.Read, Int -> DescribeSnapshotsResponse -> ShowS
[DescribeSnapshotsResponse] -> ShowS
DescribeSnapshotsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSnapshotsResponse] -> ShowS
$cshowList :: [DescribeSnapshotsResponse] -> ShowS
show :: DescribeSnapshotsResponse -> String
$cshow :: DescribeSnapshotsResponse -> String
showsPrec :: Int -> DescribeSnapshotsResponse -> ShowS
$cshowsPrec :: Int -> DescribeSnapshotsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeSnapshotsResponse x -> DescribeSnapshotsResponse
forall x.
DescribeSnapshotsResponse -> Rep DescribeSnapshotsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSnapshotsResponse x -> DescribeSnapshotsResponse
$cfrom :: forall x.
DescribeSnapshotsResponse -> Rep DescribeSnapshotsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSnapshotsResponse' 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:
--
-- 'nextToken', 'describeSnapshotsResponse_nextToken' - Undocumented member.
--
-- 'snapshots', 'describeSnapshotsResponse_snapshots' - An array of snapshots.
--
-- 'httpStatus', 'describeSnapshotsResponse_httpStatus' - The response's http status code.
newDescribeSnapshotsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeSnapshotsResponse
newDescribeSnapshotsResponse :: Int -> DescribeSnapshotsResponse
newDescribeSnapshotsResponse Int
pHttpStatus_ =
  DescribeSnapshotsResponse'
    { $sel:nextToken:DescribeSnapshotsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:snapshots:DescribeSnapshotsResponse' :: Maybe [Snapshot]
snapshots = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeSnapshotsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
describeSnapshotsResponse_nextToken :: Lens.Lens' DescribeSnapshotsResponse (Prelude.Maybe Prelude.Text)
describeSnapshotsResponse_nextToken :: Lens' DescribeSnapshotsResponse (Maybe Text)
describeSnapshotsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeSnapshotsResponse' :: DescribeSnapshotsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeSnapshotsResponse
s@DescribeSnapshotsResponse' {} Maybe Text
a -> DescribeSnapshotsResponse
s {$sel:nextToken:DescribeSnapshotsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeSnapshotsResponse)

-- | An array of snapshots.
describeSnapshotsResponse_snapshots :: Lens.Lens' DescribeSnapshotsResponse (Prelude.Maybe [Snapshot])
describeSnapshotsResponse_snapshots :: Lens' DescribeSnapshotsResponse (Maybe [Snapshot])
describeSnapshotsResponse_snapshots = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotsResponse' {Maybe [Snapshot]
snapshots :: Maybe [Snapshot]
$sel:snapshots:DescribeSnapshotsResponse' :: DescribeSnapshotsResponse -> Maybe [Snapshot]
snapshots} -> Maybe [Snapshot]
snapshots) (\s :: DescribeSnapshotsResponse
s@DescribeSnapshotsResponse' {} Maybe [Snapshot]
a -> DescribeSnapshotsResponse
s {$sel:snapshots:DescribeSnapshotsResponse' :: Maybe [Snapshot]
snapshots = Maybe [Snapshot]
a} :: DescribeSnapshotsResponse) 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.
describeSnapshotsResponse_httpStatus :: Lens.Lens' DescribeSnapshotsResponse Prelude.Int
describeSnapshotsResponse_httpStatus :: Lens' DescribeSnapshotsResponse Int
describeSnapshotsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeSnapshotsResponse' :: DescribeSnapshotsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeSnapshotsResponse
s@DescribeSnapshotsResponse' {} Int
a -> DescribeSnapshotsResponse
s {$sel:httpStatus:DescribeSnapshotsResponse' :: Int
httpStatus = Int
a} :: DescribeSnapshotsResponse)

instance Prelude.NFData DescribeSnapshotsResponse where
  rnf :: DescribeSnapshotsResponse -> ()
rnf DescribeSnapshotsResponse' {Int
Maybe [Snapshot]
Maybe Text
httpStatus :: Int
snapshots :: Maybe [Snapshot]
nextToken :: Maybe Text
$sel:httpStatus:DescribeSnapshotsResponse' :: DescribeSnapshotsResponse -> Int
$sel:snapshots:DescribeSnapshotsResponse' :: DescribeSnapshotsResponse -> Maybe [Snapshot]
$sel:nextToken:DescribeSnapshotsResponse' :: DescribeSnapshotsResponse -> Maybe Text
..} =
    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 Maybe [Snapshot]
snapshots
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus