{-# 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.Lightsail.GetRelationalDatabaseSnapshots
-- 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 information about all of your database snapshots in Amazon
-- Lightsail.
--
-- This operation returns paginated results.
module Amazonka.Lightsail.GetRelationalDatabaseSnapshots
  ( -- * Creating a Request
    GetRelationalDatabaseSnapshots (..),
    newGetRelationalDatabaseSnapshots,

    -- * Request Lenses
    getRelationalDatabaseSnapshots_pageToken,

    -- * Destructuring the Response
    GetRelationalDatabaseSnapshotsResponse (..),
    newGetRelationalDatabaseSnapshotsResponse,

    -- * Response Lenses
    getRelationalDatabaseSnapshotsResponse_nextPageToken,
    getRelationalDatabaseSnapshotsResponse_relationalDatabaseSnapshots,
    getRelationalDatabaseSnapshotsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetRelationalDatabaseSnapshots' smart constructor.
data GetRelationalDatabaseSnapshots = GetRelationalDatabaseSnapshots'
  { -- | The token to advance to the next page of results from your request.
    --
    -- To get a page token, perform an initial @GetRelationalDatabaseSnapshots@
    -- request. If your results are paginated, the response will return a next
    -- page token that you can specify as the page token in a subsequent
    -- request.
    GetRelationalDatabaseSnapshots -> Maybe Text
pageToken :: Prelude.Maybe Prelude.Text
  }
  deriving (GetRelationalDatabaseSnapshots
-> GetRelationalDatabaseSnapshots -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRelationalDatabaseSnapshots
-> GetRelationalDatabaseSnapshots -> Bool
$c/= :: GetRelationalDatabaseSnapshots
-> GetRelationalDatabaseSnapshots -> Bool
== :: GetRelationalDatabaseSnapshots
-> GetRelationalDatabaseSnapshots -> Bool
$c== :: GetRelationalDatabaseSnapshots
-> GetRelationalDatabaseSnapshots -> Bool
Prelude.Eq, ReadPrec [GetRelationalDatabaseSnapshots]
ReadPrec GetRelationalDatabaseSnapshots
Int -> ReadS GetRelationalDatabaseSnapshots
ReadS [GetRelationalDatabaseSnapshots]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRelationalDatabaseSnapshots]
$creadListPrec :: ReadPrec [GetRelationalDatabaseSnapshots]
readPrec :: ReadPrec GetRelationalDatabaseSnapshots
$creadPrec :: ReadPrec GetRelationalDatabaseSnapshots
readList :: ReadS [GetRelationalDatabaseSnapshots]
$creadList :: ReadS [GetRelationalDatabaseSnapshots]
readsPrec :: Int -> ReadS GetRelationalDatabaseSnapshots
$creadsPrec :: Int -> ReadS GetRelationalDatabaseSnapshots
Prelude.Read, Int -> GetRelationalDatabaseSnapshots -> ShowS
[GetRelationalDatabaseSnapshots] -> ShowS
GetRelationalDatabaseSnapshots -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRelationalDatabaseSnapshots] -> ShowS
$cshowList :: [GetRelationalDatabaseSnapshots] -> ShowS
show :: GetRelationalDatabaseSnapshots -> String
$cshow :: GetRelationalDatabaseSnapshots -> String
showsPrec :: Int -> GetRelationalDatabaseSnapshots -> ShowS
$cshowsPrec :: Int -> GetRelationalDatabaseSnapshots -> ShowS
Prelude.Show, forall x.
Rep GetRelationalDatabaseSnapshots x
-> GetRelationalDatabaseSnapshots
forall x.
GetRelationalDatabaseSnapshots
-> Rep GetRelationalDatabaseSnapshots x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetRelationalDatabaseSnapshots x
-> GetRelationalDatabaseSnapshots
$cfrom :: forall x.
GetRelationalDatabaseSnapshots
-> Rep GetRelationalDatabaseSnapshots x
Prelude.Generic)

-- |
-- Create a value of 'GetRelationalDatabaseSnapshots' 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:
--
-- 'pageToken', 'getRelationalDatabaseSnapshots_pageToken' - The token to advance to the next page of results from your request.
--
-- To get a page token, perform an initial @GetRelationalDatabaseSnapshots@
-- request. If your results are paginated, the response will return a next
-- page token that you can specify as the page token in a subsequent
-- request.
newGetRelationalDatabaseSnapshots ::
  GetRelationalDatabaseSnapshots
newGetRelationalDatabaseSnapshots :: GetRelationalDatabaseSnapshots
newGetRelationalDatabaseSnapshots =
  GetRelationalDatabaseSnapshots'
    { $sel:pageToken:GetRelationalDatabaseSnapshots' :: Maybe Text
pageToken =
        forall a. Maybe a
Prelude.Nothing
    }

-- | The token to advance to the next page of results from your request.
--
-- To get a page token, perform an initial @GetRelationalDatabaseSnapshots@
-- request. If your results are paginated, the response will return a next
-- page token that you can specify as the page token in a subsequent
-- request.
getRelationalDatabaseSnapshots_pageToken :: Lens.Lens' GetRelationalDatabaseSnapshots (Prelude.Maybe Prelude.Text)
getRelationalDatabaseSnapshots_pageToken :: Lens' GetRelationalDatabaseSnapshots (Maybe Text)
getRelationalDatabaseSnapshots_pageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRelationalDatabaseSnapshots' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetRelationalDatabaseSnapshots' :: GetRelationalDatabaseSnapshots -> Maybe Text
pageToken} -> Maybe Text
pageToken) (\s :: GetRelationalDatabaseSnapshots
s@GetRelationalDatabaseSnapshots' {} Maybe Text
a -> GetRelationalDatabaseSnapshots
s {$sel:pageToken:GetRelationalDatabaseSnapshots' :: Maybe Text
pageToken = Maybe Text
a} :: GetRelationalDatabaseSnapshots)

instance Core.AWSPager GetRelationalDatabaseSnapshots where
  page :: GetRelationalDatabaseSnapshots
-> AWSResponse GetRelationalDatabaseSnapshots
-> Maybe GetRelationalDatabaseSnapshots
page GetRelationalDatabaseSnapshots
rq AWSResponse GetRelationalDatabaseSnapshots
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetRelationalDatabaseSnapshots
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetRelationalDatabaseSnapshotsResponse (Maybe Text)
getRelationalDatabaseSnapshotsResponse_nextPageToken
            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 GetRelationalDatabaseSnapshots
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  GetRelationalDatabaseSnapshotsResponse
  (Maybe [RelationalDatabaseSnapshot])
getRelationalDatabaseSnapshotsResponse_relationalDatabaseSnapshots
            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.$ GetRelationalDatabaseSnapshots
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetRelationalDatabaseSnapshots (Maybe Text)
getRelationalDatabaseSnapshots_pageToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetRelationalDatabaseSnapshots
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetRelationalDatabaseSnapshotsResponse (Maybe Text)
getRelationalDatabaseSnapshotsResponse_nextPageToken
          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
    GetRelationalDatabaseSnapshots
  where
  type
    AWSResponse GetRelationalDatabaseSnapshots =
      GetRelationalDatabaseSnapshotsResponse
  request :: (Service -> Service)
-> GetRelationalDatabaseSnapshots
-> Request GetRelationalDatabaseSnapshots
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 GetRelationalDatabaseSnapshots
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetRelationalDatabaseSnapshots)))
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 [RelationalDatabaseSnapshot]
-> Int
-> GetRelationalDatabaseSnapshotsResponse
GetRelationalDatabaseSnapshotsResponse'
            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
"nextPageToken")
            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
"relationalDatabaseSnapshots"
                            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
    GetRelationalDatabaseSnapshots
  where
  hashWithSalt :: Int -> GetRelationalDatabaseSnapshots -> Int
hashWithSalt
    Int
_salt
    GetRelationalDatabaseSnapshots' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetRelationalDatabaseSnapshots' :: GetRelationalDatabaseSnapshots -> Maybe Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageToken

instance
  Prelude.NFData
    GetRelationalDatabaseSnapshots
  where
  rnf :: GetRelationalDatabaseSnapshots -> ()
rnf GetRelationalDatabaseSnapshots' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetRelationalDatabaseSnapshots' :: GetRelationalDatabaseSnapshots -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pageToken

instance
  Data.ToHeaders
    GetRelationalDatabaseSnapshots
  where
  toHeaders :: GetRelationalDatabaseSnapshots -> 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
"Lightsail_20161128.GetRelationalDatabaseSnapshots" ::
                          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 GetRelationalDatabaseSnapshots where
  toJSON :: GetRelationalDatabaseSnapshots -> Value
toJSON GetRelationalDatabaseSnapshots' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetRelationalDatabaseSnapshots' :: GetRelationalDatabaseSnapshots -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"pageToken" 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
pageToken]
      )

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

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

-- | /See:/ 'newGetRelationalDatabaseSnapshotsResponse' smart constructor.
data GetRelationalDatabaseSnapshotsResponse = GetRelationalDatabaseSnapshotsResponse'
  { -- | The token to advance to the next page of results from your request.
    --
    -- A next page token is not returned if there are no more results to
    -- display.
    --
    -- To get the next page of results, perform another
    -- @GetRelationalDatabaseSnapshots@ request and specify the next page token
    -- using the @pageToken@ parameter.
    GetRelationalDatabaseSnapshotsResponse -> Maybe Text
nextPageToken :: Prelude.Maybe Prelude.Text,
    -- | An object describing the result of your get relational database
    -- snapshots request.
    GetRelationalDatabaseSnapshotsResponse
-> Maybe [RelationalDatabaseSnapshot]
relationalDatabaseSnapshots :: Prelude.Maybe [RelationalDatabaseSnapshot],
    -- | The response's http status code.
    GetRelationalDatabaseSnapshotsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetRelationalDatabaseSnapshotsResponse
-> GetRelationalDatabaseSnapshotsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRelationalDatabaseSnapshotsResponse
-> GetRelationalDatabaseSnapshotsResponse -> Bool
$c/= :: GetRelationalDatabaseSnapshotsResponse
-> GetRelationalDatabaseSnapshotsResponse -> Bool
== :: GetRelationalDatabaseSnapshotsResponse
-> GetRelationalDatabaseSnapshotsResponse -> Bool
$c== :: GetRelationalDatabaseSnapshotsResponse
-> GetRelationalDatabaseSnapshotsResponse -> Bool
Prelude.Eq, ReadPrec [GetRelationalDatabaseSnapshotsResponse]
ReadPrec GetRelationalDatabaseSnapshotsResponse
Int -> ReadS GetRelationalDatabaseSnapshotsResponse
ReadS [GetRelationalDatabaseSnapshotsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRelationalDatabaseSnapshotsResponse]
$creadListPrec :: ReadPrec [GetRelationalDatabaseSnapshotsResponse]
readPrec :: ReadPrec GetRelationalDatabaseSnapshotsResponse
$creadPrec :: ReadPrec GetRelationalDatabaseSnapshotsResponse
readList :: ReadS [GetRelationalDatabaseSnapshotsResponse]
$creadList :: ReadS [GetRelationalDatabaseSnapshotsResponse]
readsPrec :: Int -> ReadS GetRelationalDatabaseSnapshotsResponse
$creadsPrec :: Int -> ReadS GetRelationalDatabaseSnapshotsResponse
Prelude.Read, Int -> GetRelationalDatabaseSnapshotsResponse -> ShowS
[GetRelationalDatabaseSnapshotsResponse] -> ShowS
GetRelationalDatabaseSnapshotsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRelationalDatabaseSnapshotsResponse] -> ShowS
$cshowList :: [GetRelationalDatabaseSnapshotsResponse] -> ShowS
show :: GetRelationalDatabaseSnapshotsResponse -> String
$cshow :: GetRelationalDatabaseSnapshotsResponse -> String
showsPrec :: Int -> GetRelationalDatabaseSnapshotsResponse -> ShowS
$cshowsPrec :: Int -> GetRelationalDatabaseSnapshotsResponse -> ShowS
Prelude.Show, forall x.
Rep GetRelationalDatabaseSnapshotsResponse x
-> GetRelationalDatabaseSnapshotsResponse
forall x.
GetRelationalDatabaseSnapshotsResponse
-> Rep GetRelationalDatabaseSnapshotsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetRelationalDatabaseSnapshotsResponse x
-> GetRelationalDatabaseSnapshotsResponse
$cfrom :: forall x.
GetRelationalDatabaseSnapshotsResponse
-> Rep GetRelationalDatabaseSnapshotsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetRelationalDatabaseSnapshotsResponse' 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:
--
-- 'nextPageToken', 'getRelationalDatabaseSnapshotsResponse_nextPageToken' - The token to advance to the next page of results from your request.
--
-- A next page token is not returned if there are no more results to
-- display.
--
-- To get the next page of results, perform another
-- @GetRelationalDatabaseSnapshots@ request and specify the next page token
-- using the @pageToken@ parameter.
--
-- 'relationalDatabaseSnapshots', 'getRelationalDatabaseSnapshotsResponse_relationalDatabaseSnapshots' - An object describing the result of your get relational database
-- snapshots request.
--
-- 'httpStatus', 'getRelationalDatabaseSnapshotsResponse_httpStatus' - The response's http status code.
newGetRelationalDatabaseSnapshotsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetRelationalDatabaseSnapshotsResponse
newGetRelationalDatabaseSnapshotsResponse :: Int -> GetRelationalDatabaseSnapshotsResponse
newGetRelationalDatabaseSnapshotsResponse
  Int
pHttpStatus_ =
    GetRelationalDatabaseSnapshotsResponse'
      { $sel:nextPageToken:GetRelationalDatabaseSnapshotsResponse' :: Maybe Text
nextPageToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:relationalDatabaseSnapshots:GetRelationalDatabaseSnapshotsResponse' :: Maybe [RelationalDatabaseSnapshot]
relationalDatabaseSnapshots =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetRelationalDatabaseSnapshotsResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The token to advance to the next page of results from your request.
--
-- A next page token is not returned if there are no more results to
-- display.
--
-- To get the next page of results, perform another
-- @GetRelationalDatabaseSnapshots@ request and specify the next page token
-- using the @pageToken@ parameter.
getRelationalDatabaseSnapshotsResponse_nextPageToken :: Lens.Lens' GetRelationalDatabaseSnapshotsResponse (Prelude.Maybe Prelude.Text)
getRelationalDatabaseSnapshotsResponse_nextPageToken :: Lens' GetRelationalDatabaseSnapshotsResponse (Maybe Text)
getRelationalDatabaseSnapshotsResponse_nextPageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRelationalDatabaseSnapshotsResponse' {Maybe Text
nextPageToken :: Maybe Text
$sel:nextPageToken:GetRelationalDatabaseSnapshotsResponse' :: GetRelationalDatabaseSnapshotsResponse -> Maybe Text
nextPageToken} -> Maybe Text
nextPageToken) (\s :: GetRelationalDatabaseSnapshotsResponse
s@GetRelationalDatabaseSnapshotsResponse' {} Maybe Text
a -> GetRelationalDatabaseSnapshotsResponse
s {$sel:nextPageToken:GetRelationalDatabaseSnapshotsResponse' :: Maybe Text
nextPageToken = Maybe Text
a} :: GetRelationalDatabaseSnapshotsResponse)

-- | An object describing the result of your get relational database
-- snapshots request.
getRelationalDatabaseSnapshotsResponse_relationalDatabaseSnapshots :: Lens.Lens' GetRelationalDatabaseSnapshotsResponse (Prelude.Maybe [RelationalDatabaseSnapshot])
getRelationalDatabaseSnapshotsResponse_relationalDatabaseSnapshots :: Lens'
  GetRelationalDatabaseSnapshotsResponse
  (Maybe [RelationalDatabaseSnapshot])
getRelationalDatabaseSnapshotsResponse_relationalDatabaseSnapshots = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRelationalDatabaseSnapshotsResponse' {Maybe [RelationalDatabaseSnapshot]
relationalDatabaseSnapshots :: Maybe [RelationalDatabaseSnapshot]
$sel:relationalDatabaseSnapshots:GetRelationalDatabaseSnapshotsResponse' :: GetRelationalDatabaseSnapshotsResponse
-> Maybe [RelationalDatabaseSnapshot]
relationalDatabaseSnapshots} -> Maybe [RelationalDatabaseSnapshot]
relationalDatabaseSnapshots) (\s :: GetRelationalDatabaseSnapshotsResponse
s@GetRelationalDatabaseSnapshotsResponse' {} Maybe [RelationalDatabaseSnapshot]
a -> GetRelationalDatabaseSnapshotsResponse
s {$sel:relationalDatabaseSnapshots:GetRelationalDatabaseSnapshotsResponse' :: Maybe [RelationalDatabaseSnapshot]
relationalDatabaseSnapshots = Maybe [RelationalDatabaseSnapshot]
a} :: GetRelationalDatabaseSnapshotsResponse) 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.
getRelationalDatabaseSnapshotsResponse_httpStatus :: Lens.Lens' GetRelationalDatabaseSnapshotsResponse Prelude.Int
getRelationalDatabaseSnapshotsResponse_httpStatus :: Lens' GetRelationalDatabaseSnapshotsResponse Int
getRelationalDatabaseSnapshotsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRelationalDatabaseSnapshotsResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetRelationalDatabaseSnapshotsResponse' :: GetRelationalDatabaseSnapshotsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetRelationalDatabaseSnapshotsResponse
s@GetRelationalDatabaseSnapshotsResponse' {} Int
a -> GetRelationalDatabaseSnapshotsResponse
s {$sel:httpStatus:GetRelationalDatabaseSnapshotsResponse' :: Int
httpStatus = Int
a} :: GetRelationalDatabaseSnapshotsResponse)

instance
  Prelude.NFData
    GetRelationalDatabaseSnapshotsResponse
  where
  rnf :: GetRelationalDatabaseSnapshotsResponse -> ()
rnf GetRelationalDatabaseSnapshotsResponse' {Int
Maybe [RelationalDatabaseSnapshot]
Maybe Text
httpStatus :: Int
relationalDatabaseSnapshots :: Maybe [RelationalDatabaseSnapshot]
nextPageToken :: Maybe Text
$sel:httpStatus:GetRelationalDatabaseSnapshotsResponse' :: GetRelationalDatabaseSnapshotsResponse -> Int
$sel:relationalDatabaseSnapshots:GetRelationalDatabaseSnapshotsResponse' :: GetRelationalDatabaseSnapshotsResponse
-> Maybe [RelationalDatabaseSnapshot]
$sel:nextPageToken:GetRelationalDatabaseSnapshotsResponse' :: GetRelationalDatabaseSnapshotsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextPageToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [RelationalDatabaseSnapshot]
relationalDatabaseSnapshots
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus