{-# 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.GetExportSnapshotRecords
-- 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 all export snapshot records created as a result of the
-- @export snapshot@ operation.
--
-- An export snapshot record can be used to create a new Amazon EC2
-- instance and its related resources with the
-- <https://docs.aws.amazon.com/lightsail/2016-11-28/api-reference/API_CreateCloudFormationStack.html CreateCloudFormationStack>
-- action.
--
-- This operation returns paginated results.
module Amazonka.Lightsail.GetExportSnapshotRecords
  ( -- * Creating a Request
    GetExportSnapshotRecords (..),
    newGetExportSnapshotRecords,

    -- * Request Lenses
    getExportSnapshotRecords_pageToken,

    -- * Destructuring the Response
    GetExportSnapshotRecordsResponse (..),
    newGetExportSnapshotRecordsResponse,

    -- * Response Lenses
    getExportSnapshotRecordsResponse_exportSnapshotRecords,
    getExportSnapshotRecordsResponse_nextPageToken,
    getExportSnapshotRecordsResponse_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:/ 'newGetExportSnapshotRecords' smart constructor.
data GetExportSnapshotRecords = GetExportSnapshotRecords'
  { -- | The token to advance to the next page of results from your request.
    --
    -- To get a page token, perform an initial @GetExportSnapshotRecords@
    -- 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.
    GetExportSnapshotRecords -> Maybe Text
pageToken :: Prelude.Maybe Prelude.Text
  }
  deriving (GetExportSnapshotRecords -> GetExportSnapshotRecords -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetExportSnapshotRecords -> GetExportSnapshotRecords -> Bool
$c/= :: GetExportSnapshotRecords -> GetExportSnapshotRecords -> Bool
== :: GetExportSnapshotRecords -> GetExportSnapshotRecords -> Bool
$c== :: GetExportSnapshotRecords -> GetExportSnapshotRecords -> Bool
Prelude.Eq, ReadPrec [GetExportSnapshotRecords]
ReadPrec GetExportSnapshotRecords
Int -> ReadS GetExportSnapshotRecords
ReadS [GetExportSnapshotRecords]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetExportSnapshotRecords]
$creadListPrec :: ReadPrec [GetExportSnapshotRecords]
readPrec :: ReadPrec GetExportSnapshotRecords
$creadPrec :: ReadPrec GetExportSnapshotRecords
readList :: ReadS [GetExportSnapshotRecords]
$creadList :: ReadS [GetExportSnapshotRecords]
readsPrec :: Int -> ReadS GetExportSnapshotRecords
$creadsPrec :: Int -> ReadS GetExportSnapshotRecords
Prelude.Read, Int -> GetExportSnapshotRecords -> ShowS
[GetExportSnapshotRecords] -> ShowS
GetExportSnapshotRecords -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetExportSnapshotRecords] -> ShowS
$cshowList :: [GetExportSnapshotRecords] -> ShowS
show :: GetExportSnapshotRecords -> String
$cshow :: GetExportSnapshotRecords -> String
showsPrec :: Int -> GetExportSnapshotRecords -> ShowS
$cshowsPrec :: Int -> GetExportSnapshotRecords -> ShowS
Prelude.Show, forall x.
Rep GetExportSnapshotRecords x -> GetExportSnapshotRecords
forall x.
GetExportSnapshotRecords -> Rep GetExportSnapshotRecords x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetExportSnapshotRecords x -> GetExportSnapshotRecords
$cfrom :: forall x.
GetExportSnapshotRecords -> Rep GetExportSnapshotRecords x
Prelude.Generic)

-- |
-- Create a value of 'GetExportSnapshotRecords' 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', 'getExportSnapshotRecords_pageToken' - The token to advance to the next page of results from your request.
--
-- To get a page token, perform an initial @GetExportSnapshotRecords@
-- 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.
newGetExportSnapshotRecords ::
  GetExportSnapshotRecords
newGetExportSnapshotRecords :: GetExportSnapshotRecords
newGetExportSnapshotRecords =
  GetExportSnapshotRecords'
    { $sel:pageToken:GetExportSnapshotRecords' :: 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 @GetExportSnapshotRecords@
-- 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.
getExportSnapshotRecords_pageToken :: Lens.Lens' GetExportSnapshotRecords (Prelude.Maybe Prelude.Text)
getExportSnapshotRecords_pageToken :: Lens' GetExportSnapshotRecords (Maybe Text)
getExportSnapshotRecords_pageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetExportSnapshotRecords' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetExportSnapshotRecords' :: GetExportSnapshotRecords -> Maybe Text
pageToken} -> Maybe Text
pageToken) (\s :: GetExportSnapshotRecords
s@GetExportSnapshotRecords' {} Maybe Text
a -> GetExportSnapshotRecords
s {$sel:pageToken:GetExportSnapshotRecords' :: Maybe Text
pageToken = Maybe Text
a} :: GetExportSnapshotRecords)

instance Core.AWSPager GetExportSnapshotRecords where
  page :: GetExportSnapshotRecords
-> AWSResponse GetExportSnapshotRecords
-> Maybe GetExportSnapshotRecords
page GetExportSnapshotRecords
rq AWSResponse GetExportSnapshotRecords
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetExportSnapshotRecords
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetExportSnapshotRecordsResponse (Maybe Text)
getExportSnapshotRecordsResponse_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 GetExportSnapshotRecords
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  GetExportSnapshotRecordsResponse (Maybe [ExportSnapshotRecord])
getExportSnapshotRecordsResponse_exportSnapshotRecords
            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.$ GetExportSnapshotRecords
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetExportSnapshotRecords (Maybe Text)
getExportSnapshotRecords_pageToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetExportSnapshotRecords
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetExportSnapshotRecordsResponse (Maybe Text)
getExportSnapshotRecordsResponse_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 GetExportSnapshotRecords where
  type
    AWSResponse GetExportSnapshotRecords =
      GetExportSnapshotRecordsResponse
  request :: (Service -> Service)
-> GetExportSnapshotRecords -> Request GetExportSnapshotRecords
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 GetExportSnapshotRecords
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetExportSnapshotRecords)))
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 [ExportSnapshotRecord]
-> Maybe Text -> Int -> GetExportSnapshotRecordsResponse
GetExportSnapshotRecordsResponse'
            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
"exportSnapshotRecords"
                            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.<*> (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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetExportSnapshotRecords where
  hashWithSalt :: Int -> GetExportSnapshotRecords -> Int
hashWithSalt Int
_salt GetExportSnapshotRecords' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetExportSnapshotRecords' :: GetExportSnapshotRecords -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageToken

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

instance Data.ToHeaders GetExportSnapshotRecords where
  toHeaders :: GetExportSnapshotRecords -> 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.GetExportSnapshotRecords" ::
                          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 GetExportSnapshotRecords where
  toJSON :: GetExportSnapshotRecords -> Value
toJSON GetExportSnapshotRecords' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetExportSnapshotRecords' :: GetExportSnapshotRecords -> 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 GetExportSnapshotRecords where
  toPath :: GetExportSnapshotRecords -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetExportSnapshotRecordsResponse' smart constructor.
data GetExportSnapshotRecordsResponse = GetExportSnapshotRecordsResponse'
  { -- | A list of objects describing the export snapshot records.
    GetExportSnapshotRecordsResponse -> Maybe [ExportSnapshotRecord]
exportSnapshotRecords :: Prelude.Maybe [ExportSnapshotRecord],
    -- | 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
    -- @GetExportSnapshotRecords@ request and specify the next page token using
    -- the @pageToken@ parameter.
    GetExportSnapshotRecordsResponse -> Maybe Text
nextPageToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetExportSnapshotRecordsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetExportSnapshotRecordsResponse
-> GetExportSnapshotRecordsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetExportSnapshotRecordsResponse
-> GetExportSnapshotRecordsResponse -> Bool
$c/= :: GetExportSnapshotRecordsResponse
-> GetExportSnapshotRecordsResponse -> Bool
== :: GetExportSnapshotRecordsResponse
-> GetExportSnapshotRecordsResponse -> Bool
$c== :: GetExportSnapshotRecordsResponse
-> GetExportSnapshotRecordsResponse -> Bool
Prelude.Eq, ReadPrec [GetExportSnapshotRecordsResponse]
ReadPrec GetExportSnapshotRecordsResponse
Int -> ReadS GetExportSnapshotRecordsResponse
ReadS [GetExportSnapshotRecordsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetExportSnapshotRecordsResponse]
$creadListPrec :: ReadPrec [GetExportSnapshotRecordsResponse]
readPrec :: ReadPrec GetExportSnapshotRecordsResponse
$creadPrec :: ReadPrec GetExportSnapshotRecordsResponse
readList :: ReadS [GetExportSnapshotRecordsResponse]
$creadList :: ReadS [GetExportSnapshotRecordsResponse]
readsPrec :: Int -> ReadS GetExportSnapshotRecordsResponse
$creadsPrec :: Int -> ReadS GetExportSnapshotRecordsResponse
Prelude.Read, Int -> GetExportSnapshotRecordsResponse -> ShowS
[GetExportSnapshotRecordsResponse] -> ShowS
GetExportSnapshotRecordsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetExportSnapshotRecordsResponse] -> ShowS
$cshowList :: [GetExportSnapshotRecordsResponse] -> ShowS
show :: GetExportSnapshotRecordsResponse -> String
$cshow :: GetExportSnapshotRecordsResponse -> String
showsPrec :: Int -> GetExportSnapshotRecordsResponse -> ShowS
$cshowsPrec :: Int -> GetExportSnapshotRecordsResponse -> ShowS
Prelude.Show, forall x.
Rep GetExportSnapshotRecordsResponse x
-> GetExportSnapshotRecordsResponse
forall x.
GetExportSnapshotRecordsResponse
-> Rep GetExportSnapshotRecordsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetExportSnapshotRecordsResponse x
-> GetExportSnapshotRecordsResponse
$cfrom :: forall x.
GetExportSnapshotRecordsResponse
-> Rep GetExportSnapshotRecordsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetExportSnapshotRecordsResponse' 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:
--
-- 'exportSnapshotRecords', 'getExportSnapshotRecordsResponse_exportSnapshotRecords' - A list of objects describing the export snapshot records.
--
-- 'nextPageToken', 'getExportSnapshotRecordsResponse_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
-- @GetExportSnapshotRecords@ request and specify the next page token using
-- the @pageToken@ parameter.
--
-- 'httpStatus', 'getExportSnapshotRecordsResponse_httpStatus' - The response's http status code.
newGetExportSnapshotRecordsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetExportSnapshotRecordsResponse
newGetExportSnapshotRecordsResponse :: Int -> GetExportSnapshotRecordsResponse
newGetExportSnapshotRecordsResponse Int
pHttpStatus_ =
  GetExportSnapshotRecordsResponse'
    { $sel:exportSnapshotRecords:GetExportSnapshotRecordsResponse' :: Maybe [ExportSnapshotRecord]
exportSnapshotRecords =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextPageToken:GetExportSnapshotRecordsResponse' :: Maybe Text
nextPageToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetExportSnapshotRecordsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of objects describing the export snapshot records.
getExportSnapshotRecordsResponse_exportSnapshotRecords :: Lens.Lens' GetExportSnapshotRecordsResponse (Prelude.Maybe [ExportSnapshotRecord])
getExportSnapshotRecordsResponse_exportSnapshotRecords :: Lens'
  GetExportSnapshotRecordsResponse (Maybe [ExportSnapshotRecord])
getExportSnapshotRecordsResponse_exportSnapshotRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetExportSnapshotRecordsResponse' {Maybe [ExportSnapshotRecord]
exportSnapshotRecords :: Maybe [ExportSnapshotRecord]
$sel:exportSnapshotRecords:GetExportSnapshotRecordsResponse' :: GetExportSnapshotRecordsResponse -> Maybe [ExportSnapshotRecord]
exportSnapshotRecords} -> Maybe [ExportSnapshotRecord]
exportSnapshotRecords) (\s :: GetExportSnapshotRecordsResponse
s@GetExportSnapshotRecordsResponse' {} Maybe [ExportSnapshotRecord]
a -> GetExportSnapshotRecordsResponse
s {$sel:exportSnapshotRecords:GetExportSnapshotRecordsResponse' :: Maybe [ExportSnapshotRecord]
exportSnapshotRecords = Maybe [ExportSnapshotRecord]
a} :: GetExportSnapshotRecordsResponse) 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 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
-- @GetExportSnapshotRecords@ request and specify the next page token using
-- the @pageToken@ parameter.
getExportSnapshotRecordsResponse_nextPageToken :: Lens.Lens' GetExportSnapshotRecordsResponse (Prelude.Maybe Prelude.Text)
getExportSnapshotRecordsResponse_nextPageToken :: Lens' GetExportSnapshotRecordsResponse (Maybe Text)
getExportSnapshotRecordsResponse_nextPageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetExportSnapshotRecordsResponse' {Maybe Text
nextPageToken :: Maybe Text
$sel:nextPageToken:GetExportSnapshotRecordsResponse' :: GetExportSnapshotRecordsResponse -> Maybe Text
nextPageToken} -> Maybe Text
nextPageToken) (\s :: GetExportSnapshotRecordsResponse
s@GetExportSnapshotRecordsResponse' {} Maybe Text
a -> GetExportSnapshotRecordsResponse
s {$sel:nextPageToken:GetExportSnapshotRecordsResponse' :: Maybe Text
nextPageToken = Maybe Text
a} :: GetExportSnapshotRecordsResponse)

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

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