{-# 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.CognitoSync.ListRecords
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets paginated records, optionally changed after a particular sync count
-- for a dataset and identity. With Amazon Cognito Sync, each identity has
-- access only to its own data. Thus, the credentials used to make this API
-- call need to have access to the identity data.
--
-- ListRecords can be called with temporary user credentials provided by
-- Cognito Identity or with developer credentials. You should use Cognito
-- Identity credentials to make this API call.
module Amazonka.CognitoSync.ListRecords
  ( -- * Creating a Request
    ListRecords (..),
    newListRecords,

    -- * Request Lenses
    listRecords_lastSyncCount,
    listRecords_maxResults,
    listRecords_nextToken,
    listRecords_syncSessionToken,
    listRecords_identityPoolId,
    listRecords_identityId,
    listRecords_datasetName,

    -- * Destructuring the Response
    ListRecordsResponse (..),
    newListRecordsResponse,

    -- * Response Lenses
    listRecordsResponse_count,
    listRecordsResponse_datasetDeletedAfterRequestedSyncCount,
    listRecordsResponse_datasetExists,
    listRecordsResponse_datasetSyncCount,
    listRecordsResponse_lastModifiedBy,
    listRecordsResponse_mergedDatasetNames,
    listRecordsResponse_nextToken,
    listRecordsResponse_records,
    listRecordsResponse_syncSessionToken,
    listRecordsResponse_httpStatus,
  )
where

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

-- | A request for a list of records.
--
-- /See:/ 'newListRecords' smart constructor.
data ListRecords = ListRecords'
  { -- | The last server sync count for this record.
    ListRecords -> Maybe Integer
lastSyncCount :: Prelude.Maybe Prelude.Integer,
    -- | The maximum number of results to be returned.
    ListRecords -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | A pagination token for obtaining the next page of results.
    ListRecords -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A token containing a session ID, identity ID, and expiration.
    ListRecords -> Maybe Text
syncSessionToken :: Prelude.Maybe Prelude.Text,
    -- | A name-spaced GUID (for example,
    -- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
    -- Cognito. GUID generation is unique within a region.
    ListRecords -> Text
identityPoolId :: Prelude.Text,
    -- | A name-spaced GUID (for example,
    -- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
    -- Cognito. GUID generation is unique within a region.
    ListRecords -> Text
identityId :: Prelude.Text,
    -- | A string of up to 128 characters. Allowed characters are a-z, A-Z, 0-9,
    -- \'_\' (underscore), \'-\' (dash), and \'.\' (dot).
    ListRecords -> Text
datasetName :: Prelude.Text
  }
  deriving (ListRecords -> ListRecords -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListRecords -> ListRecords -> Bool
$c/= :: ListRecords -> ListRecords -> Bool
== :: ListRecords -> ListRecords -> Bool
$c== :: ListRecords -> ListRecords -> Bool
Prelude.Eq, ReadPrec [ListRecords]
ReadPrec ListRecords
Int -> ReadS ListRecords
ReadS [ListRecords]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListRecords]
$creadListPrec :: ReadPrec [ListRecords]
readPrec :: ReadPrec ListRecords
$creadPrec :: ReadPrec ListRecords
readList :: ReadS [ListRecords]
$creadList :: ReadS [ListRecords]
readsPrec :: Int -> ReadS ListRecords
$creadsPrec :: Int -> ReadS ListRecords
Prelude.Read, Int -> ListRecords -> ShowS
[ListRecords] -> ShowS
ListRecords -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListRecords] -> ShowS
$cshowList :: [ListRecords] -> ShowS
show :: ListRecords -> String
$cshow :: ListRecords -> String
showsPrec :: Int -> ListRecords -> ShowS
$cshowsPrec :: Int -> ListRecords -> ShowS
Prelude.Show, forall x. Rep ListRecords x -> ListRecords
forall x. ListRecords -> Rep ListRecords x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListRecords x -> ListRecords
$cfrom :: forall x. ListRecords -> Rep ListRecords x
Prelude.Generic)

-- |
-- Create a value of 'ListRecords' 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:
--
-- 'lastSyncCount', 'listRecords_lastSyncCount' - The last server sync count for this record.
--
-- 'maxResults', 'listRecords_maxResults' - The maximum number of results to be returned.
--
-- 'nextToken', 'listRecords_nextToken' - A pagination token for obtaining the next page of results.
--
-- 'syncSessionToken', 'listRecords_syncSessionToken' - A token containing a session ID, identity ID, and expiration.
--
-- 'identityPoolId', 'listRecords_identityPoolId' - A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. GUID generation is unique within a region.
--
-- 'identityId', 'listRecords_identityId' - A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. GUID generation is unique within a region.
--
-- 'datasetName', 'listRecords_datasetName' - A string of up to 128 characters. Allowed characters are a-z, A-Z, 0-9,
-- \'_\' (underscore), \'-\' (dash), and \'.\' (dot).
newListRecords ::
  -- | 'identityPoolId'
  Prelude.Text ->
  -- | 'identityId'
  Prelude.Text ->
  -- | 'datasetName'
  Prelude.Text ->
  ListRecords
newListRecords :: Text -> Text -> Text -> ListRecords
newListRecords
  Text
pIdentityPoolId_
  Text
pIdentityId_
  Text
pDatasetName_ =
    ListRecords'
      { $sel:lastSyncCount:ListRecords' :: Maybe Integer
lastSyncCount = forall a. Maybe a
Prelude.Nothing,
        $sel:maxResults:ListRecords' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListRecords' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:syncSessionToken:ListRecords' :: Maybe Text
syncSessionToken = forall a. Maybe a
Prelude.Nothing,
        $sel:identityPoolId:ListRecords' :: Text
identityPoolId = Text
pIdentityPoolId_,
        $sel:identityId:ListRecords' :: Text
identityId = Text
pIdentityId_,
        $sel:datasetName:ListRecords' :: Text
datasetName = Text
pDatasetName_
      }

-- | The last server sync count for this record.
listRecords_lastSyncCount :: Lens.Lens' ListRecords (Prelude.Maybe Prelude.Integer)
listRecords_lastSyncCount :: Lens' ListRecords (Maybe Integer)
listRecords_lastSyncCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecords' {Maybe Integer
lastSyncCount :: Maybe Integer
$sel:lastSyncCount:ListRecords' :: ListRecords -> Maybe Integer
lastSyncCount} -> Maybe Integer
lastSyncCount) (\s :: ListRecords
s@ListRecords' {} Maybe Integer
a -> ListRecords
s {$sel:lastSyncCount:ListRecords' :: Maybe Integer
lastSyncCount = Maybe Integer
a} :: ListRecords)

-- | The maximum number of results to be returned.
listRecords_maxResults :: Lens.Lens' ListRecords (Prelude.Maybe Prelude.Int)
listRecords_maxResults :: Lens' ListRecords (Maybe Int)
listRecords_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecords' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:ListRecords' :: ListRecords -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: ListRecords
s@ListRecords' {} Maybe Int
a -> ListRecords
s {$sel:maxResults:ListRecords' :: Maybe Int
maxResults = Maybe Int
a} :: ListRecords)

-- | A pagination token for obtaining the next page of results.
listRecords_nextToken :: Lens.Lens' ListRecords (Prelude.Maybe Prelude.Text)
listRecords_nextToken :: Lens' ListRecords (Maybe Text)
listRecords_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecords' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListRecords' :: ListRecords -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListRecords
s@ListRecords' {} Maybe Text
a -> ListRecords
s {$sel:nextToken:ListRecords' :: Maybe Text
nextToken = Maybe Text
a} :: ListRecords)

-- | A token containing a session ID, identity ID, and expiration.
listRecords_syncSessionToken :: Lens.Lens' ListRecords (Prelude.Maybe Prelude.Text)
listRecords_syncSessionToken :: Lens' ListRecords (Maybe Text)
listRecords_syncSessionToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecords' {Maybe Text
syncSessionToken :: Maybe Text
$sel:syncSessionToken:ListRecords' :: ListRecords -> Maybe Text
syncSessionToken} -> Maybe Text
syncSessionToken) (\s :: ListRecords
s@ListRecords' {} Maybe Text
a -> ListRecords
s {$sel:syncSessionToken:ListRecords' :: Maybe Text
syncSessionToken = Maybe Text
a} :: ListRecords)

-- | A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. GUID generation is unique within a region.
listRecords_identityPoolId :: Lens.Lens' ListRecords Prelude.Text
listRecords_identityPoolId :: Lens' ListRecords Text
listRecords_identityPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecords' {Text
identityPoolId :: Text
$sel:identityPoolId:ListRecords' :: ListRecords -> Text
identityPoolId} -> Text
identityPoolId) (\s :: ListRecords
s@ListRecords' {} Text
a -> ListRecords
s {$sel:identityPoolId:ListRecords' :: Text
identityPoolId = Text
a} :: ListRecords)

-- | A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. GUID generation is unique within a region.
listRecords_identityId :: Lens.Lens' ListRecords Prelude.Text
listRecords_identityId :: Lens' ListRecords Text
listRecords_identityId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecords' {Text
identityId :: Text
$sel:identityId:ListRecords' :: ListRecords -> Text
identityId} -> Text
identityId) (\s :: ListRecords
s@ListRecords' {} Text
a -> ListRecords
s {$sel:identityId:ListRecords' :: Text
identityId = Text
a} :: ListRecords)

-- | A string of up to 128 characters. Allowed characters are a-z, A-Z, 0-9,
-- \'_\' (underscore), \'-\' (dash), and \'.\' (dot).
listRecords_datasetName :: Lens.Lens' ListRecords Prelude.Text
listRecords_datasetName :: Lens' ListRecords Text
listRecords_datasetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecords' {Text
datasetName :: Text
$sel:datasetName:ListRecords' :: ListRecords -> Text
datasetName} -> Text
datasetName) (\s :: ListRecords
s@ListRecords' {} Text
a -> ListRecords
s {$sel:datasetName:ListRecords' :: Text
datasetName = Text
a} :: ListRecords)

instance Core.AWSRequest ListRecords where
  type AWSResponse ListRecords = ListRecordsResponse
  request :: (Service -> Service) -> ListRecords -> Request ListRecords
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListRecords
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListRecords)))
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 Int
-> Maybe Bool
-> Maybe Bool
-> Maybe Integer
-> Maybe Text
-> Maybe [Text]
-> Maybe Text
-> Maybe [Record]
-> Maybe Text
-> Int
-> ListRecordsResponse
ListRecordsResponse'
            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
"Count")
            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
"DatasetDeletedAfterRequestedSyncCount")
            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
"DatasetExists")
            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
"DatasetSyncCount")
            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
"LastModifiedBy")
            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
"MergedDatasetNames"
                            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
"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
"Records" 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
"SyncSessionToken")
            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 ListRecords where
  hashWithSalt :: Int -> ListRecords -> Int
hashWithSalt Int
_salt ListRecords' {Maybe Int
Maybe Integer
Maybe Text
Text
datasetName :: Text
identityId :: Text
identityPoolId :: Text
syncSessionToken :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
lastSyncCount :: Maybe Integer
$sel:datasetName:ListRecords' :: ListRecords -> Text
$sel:identityId:ListRecords' :: ListRecords -> Text
$sel:identityPoolId:ListRecords' :: ListRecords -> Text
$sel:syncSessionToken:ListRecords' :: ListRecords -> Maybe Text
$sel:nextToken:ListRecords' :: ListRecords -> Maybe Text
$sel:maxResults:ListRecords' :: ListRecords -> Maybe Int
$sel:lastSyncCount:ListRecords' :: ListRecords -> Maybe Integer
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
lastSyncCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
syncSessionToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identityPoolId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identityId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
datasetName

instance Prelude.NFData ListRecords where
  rnf :: ListRecords -> ()
rnf ListRecords' {Maybe Int
Maybe Integer
Maybe Text
Text
datasetName :: Text
identityId :: Text
identityPoolId :: Text
syncSessionToken :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
lastSyncCount :: Maybe Integer
$sel:datasetName:ListRecords' :: ListRecords -> Text
$sel:identityId:ListRecords' :: ListRecords -> Text
$sel:identityPoolId:ListRecords' :: ListRecords -> Text
$sel:syncSessionToken:ListRecords' :: ListRecords -> Maybe Text
$sel:nextToken:ListRecords' :: ListRecords -> Maybe Text
$sel:maxResults:ListRecords' :: ListRecords -> Maybe Int
$sel:lastSyncCount:ListRecords' :: ListRecords -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
lastSyncCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
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
syncSessionToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
identityPoolId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
identityId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
datasetName

instance Data.ToHeaders ListRecords where
  toHeaders :: ListRecords -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath ListRecords where
  toPath :: ListRecords -> ByteString
toPath ListRecords' {Maybe Int
Maybe Integer
Maybe Text
Text
datasetName :: Text
identityId :: Text
identityPoolId :: Text
syncSessionToken :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
lastSyncCount :: Maybe Integer
$sel:datasetName:ListRecords' :: ListRecords -> Text
$sel:identityId:ListRecords' :: ListRecords -> Text
$sel:identityPoolId:ListRecords' :: ListRecords -> Text
$sel:syncSessionToken:ListRecords' :: ListRecords -> Maybe Text
$sel:nextToken:ListRecords' :: ListRecords -> Maybe Text
$sel:maxResults:ListRecords' :: ListRecords -> Maybe Int
$sel:lastSyncCount:ListRecords' :: ListRecords -> Maybe Integer
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/identitypools/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
identityPoolId,
        ByteString
"/identities/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
identityId,
        ByteString
"/datasets/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
datasetName,
        ByteString
"/records"
      ]

instance Data.ToQuery ListRecords where
  toQuery :: ListRecords -> QueryString
toQuery ListRecords' {Maybe Int
Maybe Integer
Maybe Text
Text
datasetName :: Text
identityId :: Text
identityPoolId :: Text
syncSessionToken :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
lastSyncCount :: Maybe Integer
$sel:datasetName:ListRecords' :: ListRecords -> Text
$sel:identityId:ListRecords' :: ListRecords -> Text
$sel:identityPoolId:ListRecords' :: ListRecords -> Text
$sel:syncSessionToken:ListRecords' :: ListRecords -> Maybe Text
$sel:nextToken:ListRecords' :: ListRecords -> Maybe Text
$sel:maxResults:ListRecords' :: ListRecords -> Maybe Int
$sel:lastSyncCount:ListRecords' :: ListRecords -> Maybe Integer
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"lastSyncCount" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Integer
lastSyncCount,
        ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"syncSessionToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
syncSessionToken
      ]

-- | Returned for a successful ListRecordsRequest.
--
-- /See:/ 'newListRecordsResponse' smart constructor.
data ListRecordsResponse = ListRecordsResponse'
  { -- | Total number of records.
    ListRecordsResponse -> Maybe Int
count :: Prelude.Maybe Prelude.Int,
    -- | A boolean value specifying whether to delete the dataset locally.
    ListRecordsResponse -> Maybe Bool
datasetDeletedAfterRequestedSyncCount :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether the dataset exists.
    ListRecordsResponse -> Maybe Bool
datasetExists :: Prelude.Maybe Prelude.Bool,
    -- | Server sync count for this dataset.
    ListRecordsResponse -> Maybe Integer
datasetSyncCount :: Prelude.Maybe Prelude.Integer,
    -- | The user\/device that made the last change to this record.
    ListRecordsResponse -> Maybe Text
lastModifiedBy :: Prelude.Maybe Prelude.Text,
    -- | Names of merged datasets.
    ListRecordsResponse -> Maybe [Text]
mergedDatasetNames :: Prelude.Maybe [Prelude.Text],
    -- | A pagination token for obtaining the next page of results.
    ListRecordsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of all records.
    ListRecordsResponse -> Maybe [Record]
records :: Prelude.Maybe [Record],
    -- | A token containing a session ID, identity ID, and expiration.
    ListRecordsResponse -> Maybe Text
syncSessionToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListRecordsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListRecordsResponse -> ListRecordsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListRecordsResponse -> ListRecordsResponse -> Bool
$c/= :: ListRecordsResponse -> ListRecordsResponse -> Bool
== :: ListRecordsResponse -> ListRecordsResponse -> Bool
$c== :: ListRecordsResponse -> ListRecordsResponse -> Bool
Prelude.Eq, ReadPrec [ListRecordsResponse]
ReadPrec ListRecordsResponse
Int -> ReadS ListRecordsResponse
ReadS [ListRecordsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListRecordsResponse]
$creadListPrec :: ReadPrec [ListRecordsResponse]
readPrec :: ReadPrec ListRecordsResponse
$creadPrec :: ReadPrec ListRecordsResponse
readList :: ReadS [ListRecordsResponse]
$creadList :: ReadS [ListRecordsResponse]
readsPrec :: Int -> ReadS ListRecordsResponse
$creadsPrec :: Int -> ReadS ListRecordsResponse
Prelude.Read, Int -> ListRecordsResponse -> ShowS
[ListRecordsResponse] -> ShowS
ListRecordsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListRecordsResponse] -> ShowS
$cshowList :: [ListRecordsResponse] -> ShowS
show :: ListRecordsResponse -> String
$cshow :: ListRecordsResponse -> String
showsPrec :: Int -> ListRecordsResponse -> ShowS
$cshowsPrec :: Int -> ListRecordsResponse -> ShowS
Prelude.Show, forall x. Rep ListRecordsResponse x -> ListRecordsResponse
forall x. ListRecordsResponse -> Rep ListRecordsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListRecordsResponse x -> ListRecordsResponse
$cfrom :: forall x. ListRecordsResponse -> Rep ListRecordsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListRecordsResponse' 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:
--
-- 'count', 'listRecordsResponse_count' - Total number of records.
--
-- 'datasetDeletedAfterRequestedSyncCount', 'listRecordsResponse_datasetDeletedAfterRequestedSyncCount' - A boolean value specifying whether to delete the dataset locally.
--
-- 'datasetExists', 'listRecordsResponse_datasetExists' - Indicates whether the dataset exists.
--
-- 'datasetSyncCount', 'listRecordsResponse_datasetSyncCount' - Server sync count for this dataset.
--
-- 'lastModifiedBy', 'listRecordsResponse_lastModifiedBy' - The user\/device that made the last change to this record.
--
-- 'mergedDatasetNames', 'listRecordsResponse_mergedDatasetNames' - Names of merged datasets.
--
-- 'nextToken', 'listRecordsResponse_nextToken' - A pagination token for obtaining the next page of results.
--
-- 'records', 'listRecordsResponse_records' - A list of all records.
--
-- 'syncSessionToken', 'listRecordsResponse_syncSessionToken' - A token containing a session ID, identity ID, and expiration.
--
-- 'httpStatus', 'listRecordsResponse_httpStatus' - The response's http status code.
newListRecordsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListRecordsResponse
newListRecordsResponse :: Int -> ListRecordsResponse
newListRecordsResponse Int
pHttpStatus_ =
  ListRecordsResponse'
    { $sel:count:ListRecordsResponse' :: Maybe Int
count = forall a. Maybe a
Prelude.Nothing,
      $sel:datasetDeletedAfterRequestedSyncCount:ListRecordsResponse' :: Maybe Bool
datasetDeletedAfterRequestedSyncCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:datasetExists:ListRecordsResponse' :: Maybe Bool
datasetExists = forall a. Maybe a
Prelude.Nothing,
      $sel:datasetSyncCount:ListRecordsResponse' :: Maybe Integer
datasetSyncCount = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedBy:ListRecordsResponse' :: Maybe Text
lastModifiedBy = forall a. Maybe a
Prelude.Nothing,
      $sel:mergedDatasetNames:ListRecordsResponse' :: Maybe [Text]
mergedDatasetNames = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListRecordsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:records:ListRecordsResponse' :: Maybe [Record]
records = forall a. Maybe a
Prelude.Nothing,
      $sel:syncSessionToken:ListRecordsResponse' :: Maybe Text
syncSessionToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListRecordsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Total number of records.
listRecordsResponse_count :: Lens.Lens' ListRecordsResponse (Prelude.Maybe Prelude.Int)
listRecordsResponse_count :: Lens' ListRecordsResponse (Maybe Int)
listRecordsResponse_count = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecordsResponse' {Maybe Int
count :: Maybe Int
$sel:count:ListRecordsResponse' :: ListRecordsResponse -> Maybe Int
count} -> Maybe Int
count) (\s :: ListRecordsResponse
s@ListRecordsResponse' {} Maybe Int
a -> ListRecordsResponse
s {$sel:count:ListRecordsResponse' :: Maybe Int
count = Maybe Int
a} :: ListRecordsResponse)

-- | A boolean value specifying whether to delete the dataset locally.
listRecordsResponse_datasetDeletedAfterRequestedSyncCount :: Lens.Lens' ListRecordsResponse (Prelude.Maybe Prelude.Bool)
listRecordsResponse_datasetDeletedAfterRequestedSyncCount :: Lens' ListRecordsResponse (Maybe Bool)
listRecordsResponse_datasetDeletedAfterRequestedSyncCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecordsResponse' {Maybe Bool
datasetDeletedAfterRequestedSyncCount :: Maybe Bool
$sel:datasetDeletedAfterRequestedSyncCount:ListRecordsResponse' :: ListRecordsResponse -> Maybe Bool
datasetDeletedAfterRequestedSyncCount} -> Maybe Bool
datasetDeletedAfterRequestedSyncCount) (\s :: ListRecordsResponse
s@ListRecordsResponse' {} Maybe Bool
a -> ListRecordsResponse
s {$sel:datasetDeletedAfterRequestedSyncCount:ListRecordsResponse' :: Maybe Bool
datasetDeletedAfterRequestedSyncCount = Maybe Bool
a} :: ListRecordsResponse)

-- | Indicates whether the dataset exists.
listRecordsResponse_datasetExists :: Lens.Lens' ListRecordsResponse (Prelude.Maybe Prelude.Bool)
listRecordsResponse_datasetExists :: Lens' ListRecordsResponse (Maybe Bool)
listRecordsResponse_datasetExists = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecordsResponse' {Maybe Bool
datasetExists :: Maybe Bool
$sel:datasetExists:ListRecordsResponse' :: ListRecordsResponse -> Maybe Bool
datasetExists} -> Maybe Bool
datasetExists) (\s :: ListRecordsResponse
s@ListRecordsResponse' {} Maybe Bool
a -> ListRecordsResponse
s {$sel:datasetExists:ListRecordsResponse' :: Maybe Bool
datasetExists = Maybe Bool
a} :: ListRecordsResponse)

-- | Server sync count for this dataset.
listRecordsResponse_datasetSyncCount :: Lens.Lens' ListRecordsResponse (Prelude.Maybe Prelude.Integer)
listRecordsResponse_datasetSyncCount :: Lens' ListRecordsResponse (Maybe Integer)
listRecordsResponse_datasetSyncCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecordsResponse' {Maybe Integer
datasetSyncCount :: Maybe Integer
$sel:datasetSyncCount:ListRecordsResponse' :: ListRecordsResponse -> Maybe Integer
datasetSyncCount} -> Maybe Integer
datasetSyncCount) (\s :: ListRecordsResponse
s@ListRecordsResponse' {} Maybe Integer
a -> ListRecordsResponse
s {$sel:datasetSyncCount:ListRecordsResponse' :: Maybe Integer
datasetSyncCount = Maybe Integer
a} :: ListRecordsResponse)

-- | The user\/device that made the last change to this record.
listRecordsResponse_lastModifiedBy :: Lens.Lens' ListRecordsResponse (Prelude.Maybe Prelude.Text)
listRecordsResponse_lastModifiedBy :: Lens' ListRecordsResponse (Maybe Text)
listRecordsResponse_lastModifiedBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecordsResponse' {Maybe Text
lastModifiedBy :: Maybe Text
$sel:lastModifiedBy:ListRecordsResponse' :: ListRecordsResponse -> Maybe Text
lastModifiedBy} -> Maybe Text
lastModifiedBy) (\s :: ListRecordsResponse
s@ListRecordsResponse' {} Maybe Text
a -> ListRecordsResponse
s {$sel:lastModifiedBy:ListRecordsResponse' :: Maybe Text
lastModifiedBy = Maybe Text
a} :: ListRecordsResponse)

-- | Names of merged datasets.
listRecordsResponse_mergedDatasetNames :: Lens.Lens' ListRecordsResponse (Prelude.Maybe [Prelude.Text])
listRecordsResponse_mergedDatasetNames :: Lens' ListRecordsResponse (Maybe [Text])
listRecordsResponse_mergedDatasetNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecordsResponse' {Maybe [Text]
mergedDatasetNames :: Maybe [Text]
$sel:mergedDatasetNames:ListRecordsResponse' :: ListRecordsResponse -> Maybe [Text]
mergedDatasetNames} -> Maybe [Text]
mergedDatasetNames) (\s :: ListRecordsResponse
s@ListRecordsResponse' {} Maybe [Text]
a -> ListRecordsResponse
s {$sel:mergedDatasetNames:ListRecordsResponse' :: Maybe [Text]
mergedDatasetNames = Maybe [Text]
a} :: ListRecordsResponse) 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

-- | A pagination token for obtaining the next page of results.
listRecordsResponse_nextToken :: Lens.Lens' ListRecordsResponse (Prelude.Maybe Prelude.Text)
listRecordsResponse_nextToken :: Lens' ListRecordsResponse (Maybe Text)
listRecordsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecordsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListRecordsResponse' :: ListRecordsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListRecordsResponse
s@ListRecordsResponse' {} Maybe Text
a -> ListRecordsResponse
s {$sel:nextToken:ListRecordsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListRecordsResponse)

-- | A list of all records.
listRecordsResponse_records :: Lens.Lens' ListRecordsResponse (Prelude.Maybe [Record])
listRecordsResponse_records :: Lens' ListRecordsResponse (Maybe [Record])
listRecordsResponse_records = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecordsResponse' {Maybe [Record]
records :: Maybe [Record]
$sel:records:ListRecordsResponse' :: ListRecordsResponse -> Maybe [Record]
records} -> Maybe [Record]
records) (\s :: ListRecordsResponse
s@ListRecordsResponse' {} Maybe [Record]
a -> ListRecordsResponse
s {$sel:records:ListRecordsResponse' :: Maybe [Record]
records = Maybe [Record]
a} :: ListRecordsResponse) 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

-- | A token containing a session ID, identity ID, and expiration.
listRecordsResponse_syncSessionToken :: Lens.Lens' ListRecordsResponse (Prelude.Maybe Prelude.Text)
listRecordsResponse_syncSessionToken :: Lens' ListRecordsResponse (Maybe Text)
listRecordsResponse_syncSessionToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRecordsResponse' {Maybe Text
syncSessionToken :: Maybe Text
$sel:syncSessionToken:ListRecordsResponse' :: ListRecordsResponse -> Maybe Text
syncSessionToken} -> Maybe Text
syncSessionToken) (\s :: ListRecordsResponse
s@ListRecordsResponse' {} Maybe Text
a -> ListRecordsResponse
s {$sel:syncSessionToken:ListRecordsResponse' :: Maybe Text
syncSessionToken = Maybe Text
a} :: ListRecordsResponse)

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

instance Prelude.NFData ListRecordsResponse where
  rnf :: ListRecordsResponse -> ()
rnf ListRecordsResponse' {Int
Maybe Bool
Maybe Int
Maybe Integer
Maybe [Text]
Maybe [Record]
Maybe Text
httpStatus :: Int
syncSessionToken :: Maybe Text
records :: Maybe [Record]
nextToken :: Maybe Text
mergedDatasetNames :: Maybe [Text]
lastModifiedBy :: Maybe Text
datasetSyncCount :: Maybe Integer
datasetExists :: Maybe Bool
datasetDeletedAfterRequestedSyncCount :: Maybe Bool
count :: Maybe Int
$sel:httpStatus:ListRecordsResponse' :: ListRecordsResponse -> Int
$sel:syncSessionToken:ListRecordsResponse' :: ListRecordsResponse -> Maybe Text
$sel:records:ListRecordsResponse' :: ListRecordsResponse -> Maybe [Record]
$sel:nextToken:ListRecordsResponse' :: ListRecordsResponse -> Maybe Text
$sel:mergedDatasetNames:ListRecordsResponse' :: ListRecordsResponse -> Maybe [Text]
$sel:lastModifiedBy:ListRecordsResponse' :: ListRecordsResponse -> Maybe Text
$sel:datasetSyncCount:ListRecordsResponse' :: ListRecordsResponse -> Maybe Integer
$sel:datasetExists:ListRecordsResponse' :: ListRecordsResponse -> Maybe Bool
$sel:datasetDeletedAfterRequestedSyncCount:ListRecordsResponse' :: ListRecordsResponse -> Maybe Bool
$sel:count:ListRecordsResponse' :: ListRecordsResponse -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
count
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
datasetDeletedAfterRequestedSyncCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
datasetExists
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
datasetSyncCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastModifiedBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
mergedDatasetNames
      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 [Record]
records
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
syncSessionToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus