{-# 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.DynamoDBStreams.GetRecords
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the stream records from a given shard.
--
-- Specify a shard iterator using the @ShardIterator@ parameter. The shard
-- iterator specifies the position in the shard from which you want to
-- start reading stream records sequentially. If there are no stream
-- records available in the portion of the shard that the iterator points
-- to, @GetRecords@ returns an empty list. Note that it might take multiple
-- calls to get to a portion of the shard that contains stream records.
--
-- @GetRecords@ can retrieve a maximum of 1 MB of data or 1000 stream
-- records, whichever comes first.
module Amazonka.DynamoDBStreams.GetRecords
  ( -- * Creating a Request
    GetRecords (..),
    newGetRecords,

    -- * Request Lenses
    getRecords_limit,
    getRecords_shardIterator,

    -- * Destructuring the Response
    GetRecordsResponse (..),
    newGetRecordsResponse,

    -- * Response Lenses
    getRecordsResponse_nextShardIterator,
    getRecordsResponse_records,
    getRecordsResponse_httpStatus,
  )
where

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

-- | Represents the input of a @GetRecords@ operation.
--
-- /See:/ 'newGetRecords' smart constructor.
data GetRecords = GetRecords'
  { -- | The maximum number of records to return from the shard. The upper limit
    -- is 1000.
    GetRecords -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | A shard iterator that was retrieved from a previous GetShardIterator
    -- operation. This iterator can be used to access the stream records in
    -- this shard.
    GetRecords -> Text
shardIterator :: Prelude.Text
  }
  deriving (GetRecords -> GetRecords -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRecords -> GetRecords -> Bool
$c/= :: GetRecords -> GetRecords -> Bool
== :: GetRecords -> GetRecords -> Bool
$c== :: GetRecords -> GetRecords -> Bool
Prelude.Eq, ReadPrec [GetRecords]
ReadPrec GetRecords
Int -> ReadS GetRecords
ReadS [GetRecords]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRecords]
$creadListPrec :: ReadPrec [GetRecords]
readPrec :: ReadPrec GetRecords
$creadPrec :: ReadPrec GetRecords
readList :: ReadS [GetRecords]
$creadList :: ReadS [GetRecords]
readsPrec :: Int -> ReadS GetRecords
$creadsPrec :: Int -> ReadS GetRecords
Prelude.Read, Int -> GetRecords -> ShowS
[GetRecords] -> ShowS
GetRecords -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRecords] -> ShowS
$cshowList :: [GetRecords] -> ShowS
show :: GetRecords -> String
$cshow :: GetRecords -> String
showsPrec :: Int -> GetRecords -> ShowS
$cshowsPrec :: Int -> GetRecords -> ShowS
Prelude.Show, forall x. Rep GetRecords x -> GetRecords
forall x. GetRecords -> Rep GetRecords x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRecords x -> GetRecords
$cfrom :: forall x. GetRecords -> Rep GetRecords x
Prelude.Generic)

-- |
-- Create a value of 'GetRecords' 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', 'getRecords_limit' - The maximum number of records to return from the shard. The upper limit
-- is 1000.
--
-- 'shardIterator', 'getRecords_shardIterator' - A shard iterator that was retrieved from a previous GetShardIterator
-- operation. This iterator can be used to access the stream records in
-- this shard.
newGetRecords ::
  -- | 'shardIterator'
  Prelude.Text ->
  GetRecords
newGetRecords :: Text -> GetRecords
newGetRecords Text
pShardIterator_ =
  GetRecords'
    { $sel:limit:GetRecords' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:shardIterator:GetRecords' :: Text
shardIterator = Text
pShardIterator_
    }

-- | The maximum number of records to return from the shard. The upper limit
-- is 1000.
getRecords_limit :: Lens.Lens' GetRecords (Prelude.Maybe Prelude.Natural)
getRecords_limit :: Lens' GetRecords (Maybe Natural)
getRecords_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRecords' {Maybe Natural
limit :: Maybe Natural
$sel:limit:GetRecords' :: GetRecords -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: GetRecords
s@GetRecords' {} Maybe Natural
a -> GetRecords
s {$sel:limit:GetRecords' :: Maybe Natural
limit = Maybe Natural
a} :: GetRecords)

-- | A shard iterator that was retrieved from a previous GetShardIterator
-- operation. This iterator can be used to access the stream records in
-- this shard.
getRecords_shardIterator :: Lens.Lens' GetRecords Prelude.Text
getRecords_shardIterator :: Lens' GetRecords Text
getRecords_shardIterator = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRecords' {Text
shardIterator :: Text
$sel:shardIterator:GetRecords' :: GetRecords -> Text
shardIterator} -> Text
shardIterator) (\s :: GetRecords
s@GetRecords' {} Text
a -> GetRecords
s {$sel:shardIterator:GetRecords' :: Text
shardIterator = Text
a} :: GetRecords)

instance Core.AWSRequest GetRecords where
  type AWSResponse GetRecords = GetRecordsResponse
  request :: (Service -> Service) -> GetRecords -> Request GetRecords
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 GetRecords
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetRecords)))
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 [Record] -> Int -> GetRecordsResponse
GetRecordsResponse'
            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
"NextShardIterator")
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetRecords where
  hashWithSalt :: Int -> GetRecords -> Int
hashWithSalt Int
_salt GetRecords' {Maybe Natural
Text
shardIterator :: Text
limit :: Maybe Natural
$sel:shardIterator:GetRecords' :: GetRecords -> Text
$sel:limit:GetRecords' :: GetRecords -> 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` Text
shardIterator

instance Prelude.NFData GetRecords where
  rnf :: GetRecords -> ()
rnf GetRecords' {Maybe Natural
Text
shardIterator :: Text
limit :: Maybe Natural
$sel:shardIterator:GetRecords' :: GetRecords -> Text
$sel:limit:GetRecords' :: GetRecords -> 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 Text
shardIterator

instance Data.ToHeaders GetRecords where
  toHeaders :: GetRecords -> 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
"DynamoDBStreams_20120810.GetRecords" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetRecords where
  toJSON :: GetRecords -> Value
toJSON GetRecords' {Maybe Natural
Text
shardIterator :: Text
limit :: Maybe Natural
$sel:shardIterator:GetRecords' :: GetRecords -> Text
$sel:limit:GetRecords' :: GetRecords -> 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,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ShardIterator" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
shardIterator)
          ]
      )

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

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

-- | Represents the output of a @GetRecords@ operation.
--
-- /See:/ 'newGetRecordsResponse' smart constructor.
data GetRecordsResponse = GetRecordsResponse'
  { -- | The next position in the shard from which to start sequentially reading
    -- stream records. If set to @null@, the shard has been closed and the
    -- requested iterator will not return any more data.
    GetRecordsResponse -> Maybe Text
nextShardIterator :: Prelude.Maybe Prelude.Text,
    -- | The stream records from the shard, which were retrieved using the shard
    -- iterator.
    GetRecordsResponse -> Maybe [Record]
records :: Prelude.Maybe [Record],
    -- | The response's http status code.
    GetRecordsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetRecordsResponse -> GetRecordsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRecordsResponse -> GetRecordsResponse -> Bool
$c/= :: GetRecordsResponse -> GetRecordsResponse -> Bool
== :: GetRecordsResponse -> GetRecordsResponse -> Bool
$c== :: GetRecordsResponse -> GetRecordsResponse -> Bool
Prelude.Eq, ReadPrec [GetRecordsResponse]
ReadPrec GetRecordsResponse
Int -> ReadS GetRecordsResponse
ReadS [GetRecordsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRecordsResponse]
$creadListPrec :: ReadPrec [GetRecordsResponse]
readPrec :: ReadPrec GetRecordsResponse
$creadPrec :: ReadPrec GetRecordsResponse
readList :: ReadS [GetRecordsResponse]
$creadList :: ReadS [GetRecordsResponse]
readsPrec :: Int -> ReadS GetRecordsResponse
$creadsPrec :: Int -> ReadS GetRecordsResponse
Prelude.Read, Int -> GetRecordsResponse -> ShowS
[GetRecordsResponse] -> ShowS
GetRecordsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRecordsResponse] -> ShowS
$cshowList :: [GetRecordsResponse] -> ShowS
show :: GetRecordsResponse -> String
$cshow :: GetRecordsResponse -> String
showsPrec :: Int -> GetRecordsResponse -> ShowS
$cshowsPrec :: Int -> GetRecordsResponse -> ShowS
Prelude.Show, forall x. Rep GetRecordsResponse x -> GetRecordsResponse
forall x. GetRecordsResponse -> Rep GetRecordsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRecordsResponse x -> GetRecordsResponse
$cfrom :: forall x. GetRecordsResponse -> Rep GetRecordsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetRecordsResponse' 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:
--
-- 'nextShardIterator', 'getRecordsResponse_nextShardIterator' - The next position in the shard from which to start sequentially reading
-- stream records. If set to @null@, the shard has been closed and the
-- requested iterator will not return any more data.
--
-- 'records', 'getRecordsResponse_records' - The stream records from the shard, which were retrieved using the shard
-- iterator.
--
-- 'httpStatus', 'getRecordsResponse_httpStatus' - The response's http status code.
newGetRecordsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetRecordsResponse
newGetRecordsResponse :: Int -> GetRecordsResponse
newGetRecordsResponse Int
pHttpStatus_ =
  GetRecordsResponse'
    { $sel:nextShardIterator:GetRecordsResponse' :: Maybe Text
nextShardIterator =
        forall a. Maybe a
Prelude.Nothing,
      $sel:records:GetRecordsResponse' :: Maybe [Record]
records = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetRecordsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The next position in the shard from which to start sequentially reading
-- stream records. If set to @null@, the shard has been closed and the
-- requested iterator will not return any more data.
getRecordsResponse_nextShardIterator :: Lens.Lens' GetRecordsResponse (Prelude.Maybe Prelude.Text)
getRecordsResponse_nextShardIterator :: Lens' GetRecordsResponse (Maybe Text)
getRecordsResponse_nextShardIterator = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRecordsResponse' {Maybe Text
nextShardIterator :: Maybe Text
$sel:nextShardIterator:GetRecordsResponse' :: GetRecordsResponse -> Maybe Text
nextShardIterator} -> Maybe Text
nextShardIterator) (\s :: GetRecordsResponse
s@GetRecordsResponse' {} Maybe Text
a -> GetRecordsResponse
s {$sel:nextShardIterator:GetRecordsResponse' :: Maybe Text
nextShardIterator = Maybe Text
a} :: GetRecordsResponse)

-- | The stream records from the shard, which were retrieved using the shard
-- iterator.
getRecordsResponse_records :: Lens.Lens' GetRecordsResponse (Prelude.Maybe [Record])
getRecordsResponse_records :: Lens' GetRecordsResponse (Maybe [Record])
getRecordsResponse_records = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRecordsResponse' {Maybe [Record]
records :: Maybe [Record]
$sel:records:GetRecordsResponse' :: GetRecordsResponse -> Maybe [Record]
records} -> Maybe [Record]
records) (\s :: GetRecordsResponse
s@GetRecordsResponse' {} Maybe [Record]
a -> GetRecordsResponse
s {$sel:records:GetRecordsResponse' :: Maybe [Record]
records = Maybe [Record]
a} :: GetRecordsResponse) 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.
getRecordsResponse_httpStatus :: Lens.Lens' GetRecordsResponse Prelude.Int
getRecordsResponse_httpStatus :: Lens' GetRecordsResponse Int
getRecordsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRecordsResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetRecordsResponse' :: GetRecordsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetRecordsResponse
s@GetRecordsResponse' {} Int
a -> GetRecordsResponse
s {$sel:httpStatus:GetRecordsResponse' :: Int
httpStatus = Int
a} :: GetRecordsResponse)

instance Prelude.NFData GetRecordsResponse where
  rnf :: GetRecordsResponse -> ()
rnf GetRecordsResponse' {Int
Maybe [Record]
Maybe Text
httpStatus :: Int
records :: Maybe [Record]
nextShardIterator :: Maybe Text
$sel:httpStatus:GetRecordsResponse' :: GetRecordsResponse -> Int
$sel:records:GetRecordsResponse' :: GetRecordsResponse -> Maybe [Record]
$sel:nextShardIterator:GetRecordsResponse' :: GetRecordsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextShardIterator
      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 Int
httpStatus