{-# 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.KinesisAnalyticsV2.ListApplicationSnapshots
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists information about the current application snapshots.
--
-- This operation returns paginated results.
module Amazonka.KinesisAnalyticsV2.ListApplicationSnapshots
  ( -- * Creating a Request
    ListApplicationSnapshots (..),
    newListApplicationSnapshots,

    -- * Request Lenses
    listApplicationSnapshots_limit,
    listApplicationSnapshots_nextToken,
    listApplicationSnapshots_applicationName,

    -- * Destructuring the Response
    ListApplicationSnapshotsResponse (..),
    newListApplicationSnapshotsResponse,

    -- * Response Lenses
    listApplicationSnapshotsResponse_nextToken,
    listApplicationSnapshotsResponse_snapshotSummaries,
    listApplicationSnapshotsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListApplicationSnapshots' smart constructor.
data ListApplicationSnapshots = ListApplicationSnapshots'
  { -- | The maximum number of application snapshots to list.
    ListApplicationSnapshots -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | Use this parameter if you receive a @NextToken@ response in a previous
    -- request that indicates that there is more output available. Set it to
    -- the value of the previous call\'s @NextToken@ response to indicate where
    -- the output should continue from.
    ListApplicationSnapshots -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of an existing application.
    ListApplicationSnapshots -> Text
applicationName :: Prelude.Text
  }
  deriving (ListApplicationSnapshots -> ListApplicationSnapshots -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApplicationSnapshots -> ListApplicationSnapshots -> Bool
$c/= :: ListApplicationSnapshots -> ListApplicationSnapshots -> Bool
== :: ListApplicationSnapshots -> ListApplicationSnapshots -> Bool
$c== :: ListApplicationSnapshots -> ListApplicationSnapshots -> Bool
Prelude.Eq, ReadPrec [ListApplicationSnapshots]
ReadPrec ListApplicationSnapshots
Int -> ReadS ListApplicationSnapshots
ReadS [ListApplicationSnapshots]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApplicationSnapshots]
$creadListPrec :: ReadPrec [ListApplicationSnapshots]
readPrec :: ReadPrec ListApplicationSnapshots
$creadPrec :: ReadPrec ListApplicationSnapshots
readList :: ReadS [ListApplicationSnapshots]
$creadList :: ReadS [ListApplicationSnapshots]
readsPrec :: Int -> ReadS ListApplicationSnapshots
$creadsPrec :: Int -> ReadS ListApplicationSnapshots
Prelude.Read, Int -> ListApplicationSnapshots -> ShowS
[ListApplicationSnapshots] -> ShowS
ListApplicationSnapshots -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApplicationSnapshots] -> ShowS
$cshowList :: [ListApplicationSnapshots] -> ShowS
show :: ListApplicationSnapshots -> String
$cshow :: ListApplicationSnapshots -> String
showsPrec :: Int -> ListApplicationSnapshots -> ShowS
$cshowsPrec :: Int -> ListApplicationSnapshots -> ShowS
Prelude.Show, forall x.
Rep ListApplicationSnapshots x -> ListApplicationSnapshots
forall x.
ListApplicationSnapshots -> Rep ListApplicationSnapshots x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApplicationSnapshots x -> ListApplicationSnapshots
$cfrom :: forall x.
ListApplicationSnapshots -> Rep ListApplicationSnapshots x
Prelude.Generic)

-- |
-- Create a value of 'ListApplicationSnapshots' 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:
--
-- 'limit', 'listApplicationSnapshots_limit' - The maximum number of application snapshots to list.
--
-- 'nextToken', 'listApplicationSnapshots_nextToken' - Use this parameter if you receive a @NextToken@ response in a previous
-- request that indicates that there is more output available. Set it to
-- the value of the previous call\'s @NextToken@ response to indicate where
-- the output should continue from.
--
-- 'applicationName', 'listApplicationSnapshots_applicationName' - The name of an existing application.
newListApplicationSnapshots ::
  -- | 'applicationName'
  Prelude.Text ->
  ListApplicationSnapshots
newListApplicationSnapshots :: Text -> ListApplicationSnapshots
newListApplicationSnapshots Text
pApplicationName_ =
  ListApplicationSnapshots'
    { $sel:limit:ListApplicationSnapshots' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListApplicationSnapshots' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:applicationName:ListApplicationSnapshots' :: Text
applicationName = Text
pApplicationName_
    }

-- | The maximum number of application snapshots to list.
listApplicationSnapshots_limit :: Lens.Lens' ListApplicationSnapshots (Prelude.Maybe Prelude.Natural)
listApplicationSnapshots_limit :: Lens' ListApplicationSnapshots (Maybe Natural)
listApplicationSnapshots_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationSnapshots' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListApplicationSnapshots' :: ListApplicationSnapshots -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListApplicationSnapshots
s@ListApplicationSnapshots' {} Maybe Natural
a -> ListApplicationSnapshots
s {$sel:limit:ListApplicationSnapshots' :: Maybe Natural
limit = Maybe Natural
a} :: ListApplicationSnapshots)

-- | Use this parameter if you receive a @NextToken@ response in a previous
-- request that indicates that there is more output available. Set it to
-- the value of the previous call\'s @NextToken@ response to indicate where
-- the output should continue from.
listApplicationSnapshots_nextToken :: Lens.Lens' ListApplicationSnapshots (Prelude.Maybe Prelude.Text)
listApplicationSnapshots_nextToken :: Lens' ListApplicationSnapshots (Maybe Text)
listApplicationSnapshots_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationSnapshots' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApplicationSnapshots' :: ListApplicationSnapshots -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApplicationSnapshots
s@ListApplicationSnapshots' {} Maybe Text
a -> ListApplicationSnapshots
s {$sel:nextToken:ListApplicationSnapshots' :: Maybe Text
nextToken = Maybe Text
a} :: ListApplicationSnapshots)

-- | The name of an existing application.
listApplicationSnapshots_applicationName :: Lens.Lens' ListApplicationSnapshots Prelude.Text
listApplicationSnapshots_applicationName :: Lens' ListApplicationSnapshots Text
listApplicationSnapshots_applicationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationSnapshots' {Text
applicationName :: Text
$sel:applicationName:ListApplicationSnapshots' :: ListApplicationSnapshots -> Text
applicationName} -> Text
applicationName) (\s :: ListApplicationSnapshots
s@ListApplicationSnapshots' {} Text
a -> ListApplicationSnapshots
s {$sel:applicationName:ListApplicationSnapshots' :: Text
applicationName = Text
a} :: ListApplicationSnapshots)

instance Core.AWSPager ListApplicationSnapshots where
  page :: ListApplicationSnapshots
-> AWSResponse ListApplicationSnapshots
-> Maybe ListApplicationSnapshots
page ListApplicationSnapshots
rq AWSResponse ListApplicationSnapshots
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListApplicationSnapshots
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListApplicationSnapshotsResponse (Maybe Text)
listApplicationSnapshotsResponse_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 ListApplicationSnapshots
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListApplicationSnapshotsResponse (Maybe [SnapshotDetails])
listApplicationSnapshotsResponse_snapshotSummaries
            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.$ ListApplicationSnapshots
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListApplicationSnapshots (Maybe Text)
listApplicationSnapshots_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListApplicationSnapshots
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListApplicationSnapshotsResponse (Maybe Text)
listApplicationSnapshotsResponse_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 ListApplicationSnapshots where
  type
    AWSResponse ListApplicationSnapshots =
      ListApplicationSnapshotsResponse
  request :: (Service -> Service)
-> ListApplicationSnapshots -> Request ListApplicationSnapshots
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 ListApplicationSnapshots
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListApplicationSnapshots)))
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 [SnapshotDetails]
-> Int
-> ListApplicationSnapshotsResponse
ListApplicationSnapshotsResponse'
            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
"SnapshotSummaries"
                            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 ListApplicationSnapshots where
  hashWithSalt :: Int -> ListApplicationSnapshots -> Int
hashWithSalt Int
_salt ListApplicationSnapshots' {Maybe Natural
Maybe Text
Text
applicationName :: Text
nextToken :: Maybe Text
limit :: Maybe Natural
$sel:applicationName:ListApplicationSnapshots' :: ListApplicationSnapshots -> Text
$sel:nextToken:ListApplicationSnapshots' :: ListApplicationSnapshots -> Maybe Text
$sel:limit:ListApplicationSnapshots' :: ListApplicationSnapshots -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationName

instance Prelude.NFData ListApplicationSnapshots where
  rnf :: ListApplicationSnapshots -> ()
rnf ListApplicationSnapshots' {Maybe Natural
Maybe Text
Text
applicationName :: Text
nextToken :: Maybe Text
limit :: Maybe Natural
$sel:applicationName:ListApplicationSnapshots' :: ListApplicationSnapshots -> Text
$sel:nextToken:ListApplicationSnapshots' :: ListApplicationSnapshots -> Maybe Text
$sel:limit:ListApplicationSnapshots' :: ListApplicationSnapshots -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      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 Text
applicationName

instance Data.ToHeaders ListApplicationSnapshots where
  toHeaders :: ListApplicationSnapshots -> 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
"KinesisAnalytics_20180523.ListApplicationSnapshots" ::
                          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 ListApplicationSnapshots where
  toJSON :: ListApplicationSnapshots -> Value
toJSON ListApplicationSnapshots' {Maybe Natural
Maybe Text
Text
applicationName :: Text
nextToken :: Maybe Text
limit :: Maybe Natural
$sel:applicationName:ListApplicationSnapshots' :: ListApplicationSnapshots -> Text
$sel:nextToken:ListApplicationSnapshots' :: ListApplicationSnapshots -> Maybe Text
$sel:limit:ListApplicationSnapshots' :: ListApplicationSnapshots -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Limit" 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
limit,
            (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,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ApplicationName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
applicationName)
          ]
      )

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

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

-- | /See:/ 'newListApplicationSnapshotsResponse' smart constructor.
data ListApplicationSnapshotsResponse = ListApplicationSnapshotsResponse'
  { -- | The token for the next set of results, or @null@ if there are no
    -- additional results.
    ListApplicationSnapshotsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A collection of objects containing information about the application
    -- snapshots.
    ListApplicationSnapshotsResponse -> Maybe [SnapshotDetails]
snapshotSummaries :: Prelude.Maybe [SnapshotDetails],
    -- | The response's http status code.
    ListApplicationSnapshotsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListApplicationSnapshotsResponse
-> ListApplicationSnapshotsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApplicationSnapshotsResponse
-> ListApplicationSnapshotsResponse -> Bool
$c/= :: ListApplicationSnapshotsResponse
-> ListApplicationSnapshotsResponse -> Bool
== :: ListApplicationSnapshotsResponse
-> ListApplicationSnapshotsResponse -> Bool
$c== :: ListApplicationSnapshotsResponse
-> ListApplicationSnapshotsResponse -> Bool
Prelude.Eq, ReadPrec [ListApplicationSnapshotsResponse]
ReadPrec ListApplicationSnapshotsResponse
Int -> ReadS ListApplicationSnapshotsResponse
ReadS [ListApplicationSnapshotsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApplicationSnapshotsResponse]
$creadListPrec :: ReadPrec [ListApplicationSnapshotsResponse]
readPrec :: ReadPrec ListApplicationSnapshotsResponse
$creadPrec :: ReadPrec ListApplicationSnapshotsResponse
readList :: ReadS [ListApplicationSnapshotsResponse]
$creadList :: ReadS [ListApplicationSnapshotsResponse]
readsPrec :: Int -> ReadS ListApplicationSnapshotsResponse
$creadsPrec :: Int -> ReadS ListApplicationSnapshotsResponse
Prelude.Read, Int -> ListApplicationSnapshotsResponse -> ShowS
[ListApplicationSnapshotsResponse] -> ShowS
ListApplicationSnapshotsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApplicationSnapshotsResponse] -> ShowS
$cshowList :: [ListApplicationSnapshotsResponse] -> ShowS
show :: ListApplicationSnapshotsResponse -> String
$cshow :: ListApplicationSnapshotsResponse -> String
showsPrec :: Int -> ListApplicationSnapshotsResponse -> ShowS
$cshowsPrec :: Int -> ListApplicationSnapshotsResponse -> ShowS
Prelude.Show, forall x.
Rep ListApplicationSnapshotsResponse x
-> ListApplicationSnapshotsResponse
forall x.
ListApplicationSnapshotsResponse
-> Rep ListApplicationSnapshotsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApplicationSnapshotsResponse x
-> ListApplicationSnapshotsResponse
$cfrom :: forall x.
ListApplicationSnapshotsResponse
-> Rep ListApplicationSnapshotsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListApplicationSnapshotsResponse' 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', 'listApplicationSnapshotsResponse_nextToken' - The token for the next set of results, or @null@ if there are no
-- additional results.
--
-- 'snapshotSummaries', 'listApplicationSnapshotsResponse_snapshotSummaries' - A collection of objects containing information about the application
-- snapshots.
--
-- 'httpStatus', 'listApplicationSnapshotsResponse_httpStatus' - The response's http status code.
newListApplicationSnapshotsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListApplicationSnapshotsResponse
newListApplicationSnapshotsResponse :: Int -> ListApplicationSnapshotsResponse
newListApplicationSnapshotsResponse Int
pHttpStatus_ =
  ListApplicationSnapshotsResponse'
    { $sel:nextToken:ListApplicationSnapshotsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotSummaries:ListApplicationSnapshotsResponse' :: Maybe [SnapshotDetails]
snapshotSummaries = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListApplicationSnapshotsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The token for the next set of results, or @null@ if there are no
-- additional results.
listApplicationSnapshotsResponse_nextToken :: Lens.Lens' ListApplicationSnapshotsResponse (Prelude.Maybe Prelude.Text)
listApplicationSnapshotsResponse_nextToken :: Lens' ListApplicationSnapshotsResponse (Maybe Text)
listApplicationSnapshotsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationSnapshotsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApplicationSnapshotsResponse' :: ListApplicationSnapshotsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApplicationSnapshotsResponse
s@ListApplicationSnapshotsResponse' {} Maybe Text
a -> ListApplicationSnapshotsResponse
s {$sel:nextToken:ListApplicationSnapshotsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListApplicationSnapshotsResponse)

-- | A collection of objects containing information about the application
-- snapshots.
listApplicationSnapshotsResponse_snapshotSummaries :: Lens.Lens' ListApplicationSnapshotsResponse (Prelude.Maybe [SnapshotDetails])
listApplicationSnapshotsResponse_snapshotSummaries :: Lens' ListApplicationSnapshotsResponse (Maybe [SnapshotDetails])
listApplicationSnapshotsResponse_snapshotSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationSnapshotsResponse' {Maybe [SnapshotDetails]
snapshotSummaries :: Maybe [SnapshotDetails]
$sel:snapshotSummaries:ListApplicationSnapshotsResponse' :: ListApplicationSnapshotsResponse -> Maybe [SnapshotDetails]
snapshotSummaries} -> Maybe [SnapshotDetails]
snapshotSummaries) (\s :: ListApplicationSnapshotsResponse
s@ListApplicationSnapshotsResponse' {} Maybe [SnapshotDetails]
a -> ListApplicationSnapshotsResponse
s {$sel:snapshotSummaries:ListApplicationSnapshotsResponse' :: Maybe [SnapshotDetails]
snapshotSummaries = Maybe [SnapshotDetails]
a} :: ListApplicationSnapshotsResponse) 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.
listApplicationSnapshotsResponse_httpStatus :: Lens.Lens' ListApplicationSnapshotsResponse Prelude.Int
listApplicationSnapshotsResponse_httpStatus :: Lens' ListApplicationSnapshotsResponse Int
listApplicationSnapshotsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationSnapshotsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListApplicationSnapshotsResponse' :: ListApplicationSnapshotsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListApplicationSnapshotsResponse
s@ListApplicationSnapshotsResponse' {} Int
a -> ListApplicationSnapshotsResponse
s {$sel:httpStatus:ListApplicationSnapshotsResponse' :: Int
httpStatus = Int
a} :: ListApplicationSnapshotsResponse)

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