{-# 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.ListStreams
-- 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 an array of stream ARNs associated with the current account and
-- endpoint. If the @TableName@ parameter is present, then @ListStreams@
-- will return only the streams ARNs for that table.
--
-- You can call @ListStreams@ at a maximum rate of 5 times per second.
module Amazonka.DynamoDBStreams.ListStreams
  ( -- * Creating a Request
    ListStreams (..),
    newListStreams,

    -- * Request Lenses
    listStreams_exclusiveStartStreamArn,
    listStreams_limit,
    listStreams_tableName,

    -- * Destructuring the Response
    ListStreamsResponse (..),
    newListStreamsResponse,

    -- * Response Lenses
    listStreamsResponse_lastEvaluatedStreamArn,
    listStreamsResponse_streams,
    listStreamsResponse_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 @ListStreams@ operation.
--
-- /See:/ 'newListStreams' smart constructor.
data ListStreams = ListStreams'
  { -- | The ARN (Amazon Resource Name) of the first item that this operation
    -- will evaluate. Use the value that was returned for
    -- @LastEvaluatedStreamArn@ in the previous operation.
    ListStreams -> Maybe Text
exclusiveStartStreamArn :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of streams to return. The upper limit is 100.
    ListStreams -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | If this parameter is provided, then only the streams associated with
    -- this table name are returned.
    ListStreams -> Maybe Text
tableName :: Prelude.Maybe Prelude.Text
  }
  deriving (ListStreams -> ListStreams -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListStreams -> ListStreams -> Bool
$c/= :: ListStreams -> ListStreams -> Bool
== :: ListStreams -> ListStreams -> Bool
$c== :: ListStreams -> ListStreams -> Bool
Prelude.Eq, ReadPrec [ListStreams]
ReadPrec ListStreams
Int -> ReadS ListStreams
ReadS [ListStreams]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListStreams]
$creadListPrec :: ReadPrec [ListStreams]
readPrec :: ReadPrec ListStreams
$creadPrec :: ReadPrec ListStreams
readList :: ReadS [ListStreams]
$creadList :: ReadS [ListStreams]
readsPrec :: Int -> ReadS ListStreams
$creadsPrec :: Int -> ReadS ListStreams
Prelude.Read, Int -> ListStreams -> ShowS
[ListStreams] -> ShowS
ListStreams -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListStreams] -> ShowS
$cshowList :: [ListStreams] -> ShowS
show :: ListStreams -> String
$cshow :: ListStreams -> String
showsPrec :: Int -> ListStreams -> ShowS
$cshowsPrec :: Int -> ListStreams -> ShowS
Prelude.Show, forall x. Rep ListStreams x -> ListStreams
forall x. ListStreams -> Rep ListStreams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListStreams x -> ListStreams
$cfrom :: forall x. ListStreams -> Rep ListStreams x
Prelude.Generic)

-- |
-- Create a value of 'ListStreams' 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:
--
-- 'exclusiveStartStreamArn', 'listStreams_exclusiveStartStreamArn' - The ARN (Amazon Resource Name) of the first item that this operation
-- will evaluate. Use the value that was returned for
-- @LastEvaluatedStreamArn@ in the previous operation.
--
-- 'limit', 'listStreams_limit' - The maximum number of streams to return. The upper limit is 100.
--
-- 'tableName', 'listStreams_tableName' - If this parameter is provided, then only the streams associated with
-- this table name are returned.
newListStreams ::
  ListStreams
newListStreams :: ListStreams
newListStreams =
  ListStreams'
    { $sel:exclusiveStartStreamArn:ListStreams' :: Maybe Text
exclusiveStartStreamArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:limit:ListStreams' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:tableName:ListStreams' :: Maybe Text
tableName = forall a. Maybe a
Prelude.Nothing
    }

-- | The ARN (Amazon Resource Name) of the first item that this operation
-- will evaluate. Use the value that was returned for
-- @LastEvaluatedStreamArn@ in the previous operation.
listStreams_exclusiveStartStreamArn :: Lens.Lens' ListStreams (Prelude.Maybe Prelude.Text)
listStreams_exclusiveStartStreamArn :: Lens' ListStreams (Maybe Text)
listStreams_exclusiveStartStreamArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreams' {Maybe Text
exclusiveStartStreamArn :: Maybe Text
$sel:exclusiveStartStreamArn:ListStreams' :: ListStreams -> Maybe Text
exclusiveStartStreamArn} -> Maybe Text
exclusiveStartStreamArn) (\s :: ListStreams
s@ListStreams' {} Maybe Text
a -> ListStreams
s {$sel:exclusiveStartStreamArn:ListStreams' :: Maybe Text
exclusiveStartStreamArn = Maybe Text
a} :: ListStreams)

-- | The maximum number of streams to return. The upper limit is 100.
listStreams_limit :: Lens.Lens' ListStreams (Prelude.Maybe Prelude.Natural)
listStreams_limit :: Lens' ListStreams (Maybe Natural)
listStreams_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreams' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListStreams' :: ListStreams -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListStreams
s@ListStreams' {} Maybe Natural
a -> ListStreams
s {$sel:limit:ListStreams' :: Maybe Natural
limit = Maybe Natural
a} :: ListStreams)

-- | If this parameter is provided, then only the streams associated with
-- this table name are returned.
listStreams_tableName :: Lens.Lens' ListStreams (Prelude.Maybe Prelude.Text)
listStreams_tableName :: Lens' ListStreams (Maybe Text)
listStreams_tableName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreams' {Maybe Text
tableName :: Maybe Text
$sel:tableName:ListStreams' :: ListStreams -> Maybe Text
tableName} -> Maybe Text
tableName) (\s :: ListStreams
s@ListStreams' {} Maybe Text
a -> ListStreams
s {$sel:tableName:ListStreams' :: Maybe Text
tableName = Maybe Text
a} :: ListStreams)

instance Core.AWSRequest ListStreams where
  type AWSResponse ListStreams = ListStreamsResponse
  request :: (Service -> Service) -> ListStreams -> Request ListStreams
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 ListStreams
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListStreams)))
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 [Stream] -> Int -> ListStreamsResponse
ListStreamsResponse'
            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
"LastEvaluatedStreamArn")
            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
"Streams" 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 ListStreams where
  hashWithSalt :: Int -> ListStreams -> Int
hashWithSalt Int
_salt ListStreams' {Maybe Natural
Maybe Text
tableName :: Maybe Text
limit :: Maybe Natural
exclusiveStartStreamArn :: Maybe Text
$sel:tableName:ListStreams' :: ListStreams -> Maybe Text
$sel:limit:ListStreams' :: ListStreams -> Maybe Natural
$sel:exclusiveStartStreamArn:ListStreams' :: ListStreams -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
exclusiveStartStreamArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tableName

instance Prelude.NFData ListStreams where
  rnf :: ListStreams -> ()
rnf ListStreams' {Maybe Natural
Maybe Text
tableName :: Maybe Text
limit :: Maybe Natural
exclusiveStartStreamArn :: Maybe Text
$sel:tableName:ListStreams' :: ListStreams -> Maybe Text
$sel:limit:ListStreams' :: ListStreams -> Maybe Natural
$sel:exclusiveStartStreamArn:ListStreams' :: ListStreams -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
exclusiveStartStreamArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tableName

instance Data.ToHeaders ListStreams where
  toHeaders :: ListStreams -> 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.ListStreams" ::
                          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 ListStreams where
  toJSON :: ListStreams -> Value
toJSON ListStreams' {Maybe Natural
Maybe Text
tableName :: Maybe Text
limit :: Maybe Natural
exclusiveStartStreamArn :: Maybe Text
$sel:tableName:ListStreams' :: ListStreams -> Maybe Text
$sel:limit:ListStreams' :: ListStreams -> Maybe Natural
$sel:exclusiveStartStreamArn:ListStreams' :: ListStreams -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ExclusiveStartStreamArn" 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
exclusiveStartStreamArn,
            (Key
"Limit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
limit,
            (Key
"TableName" 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
tableName
          ]
      )

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

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

-- | Represents the output of a @ListStreams@ operation.
--
-- /See:/ 'newListStreamsResponse' smart constructor.
data ListStreamsResponse = ListStreamsResponse'
  { -- | The stream ARN of the item where the operation stopped, inclusive of the
    -- previous result set. Use this value to start a new operation, excluding
    -- this value in the new request.
    --
    -- If @LastEvaluatedStreamArn@ is empty, then the \"last page\" of results
    -- has been processed and there is no more data to be retrieved.
    --
    -- If @LastEvaluatedStreamArn@ is not empty, it does not necessarily mean
    -- that there is more data in the result set. The only way to know when you
    -- have reached the end of the result set is when @LastEvaluatedStreamArn@
    -- is empty.
    ListStreamsResponse -> Maybe Text
lastEvaluatedStreamArn :: Prelude.Maybe Prelude.Text,
    -- | A list of stream descriptors associated with the current account and
    -- endpoint.
    ListStreamsResponse -> Maybe [Stream]
streams :: Prelude.Maybe [Stream],
    -- | The response's http status code.
    ListStreamsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListStreamsResponse -> ListStreamsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListStreamsResponse -> ListStreamsResponse -> Bool
$c/= :: ListStreamsResponse -> ListStreamsResponse -> Bool
== :: ListStreamsResponse -> ListStreamsResponse -> Bool
$c== :: ListStreamsResponse -> ListStreamsResponse -> Bool
Prelude.Eq, ReadPrec [ListStreamsResponse]
ReadPrec ListStreamsResponse
Int -> ReadS ListStreamsResponse
ReadS [ListStreamsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListStreamsResponse]
$creadListPrec :: ReadPrec [ListStreamsResponse]
readPrec :: ReadPrec ListStreamsResponse
$creadPrec :: ReadPrec ListStreamsResponse
readList :: ReadS [ListStreamsResponse]
$creadList :: ReadS [ListStreamsResponse]
readsPrec :: Int -> ReadS ListStreamsResponse
$creadsPrec :: Int -> ReadS ListStreamsResponse
Prelude.Read, Int -> ListStreamsResponse -> ShowS
[ListStreamsResponse] -> ShowS
ListStreamsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListStreamsResponse] -> ShowS
$cshowList :: [ListStreamsResponse] -> ShowS
show :: ListStreamsResponse -> String
$cshow :: ListStreamsResponse -> String
showsPrec :: Int -> ListStreamsResponse -> ShowS
$cshowsPrec :: Int -> ListStreamsResponse -> ShowS
Prelude.Show, forall x. Rep ListStreamsResponse x -> ListStreamsResponse
forall x. ListStreamsResponse -> Rep ListStreamsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListStreamsResponse x -> ListStreamsResponse
$cfrom :: forall x. ListStreamsResponse -> Rep ListStreamsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListStreamsResponse' 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:
--
-- 'lastEvaluatedStreamArn', 'listStreamsResponse_lastEvaluatedStreamArn' - The stream ARN of the item where the operation stopped, inclusive of the
-- previous result set. Use this value to start a new operation, excluding
-- this value in the new request.
--
-- If @LastEvaluatedStreamArn@ is empty, then the \"last page\" of results
-- has been processed and there is no more data to be retrieved.
--
-- If @LastEvaluatedStreamArn@ is not empty, it does not necessarily mean
-- that there is more data in the result set. The only way to know when you
-- have reached the end of the result set is when @LastEvaluatedStreamArn@
-- is empty.
--
-- 'streams', 'listStreamsResponse_streams' - A list of stream descriptors associated with the current account and
-- endpoint.
--
-- 'httpStatus', 'listStreamsResponse_httpStatus' - The response's http status code.
newListStreamsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListStreamsResponse
newListStreamsResponse :: Int -> ListStreamsResponse
newListStreamsResponse Int
pHttpStatus_ =
  ListStreamsResponse'
    { $sel:lastEvaluatedStreamArn:ListStreamsResponse' :: Maybe Text
lastEvaluatedStreamArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:streams:ListStreamsResponse' :: Maybe [Stream]
streams = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListStreamsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The stream ARN of the item where the operation stopped, inclusive of the
-- previous result set. Use this value to start a new operation, excluding
-- this value in the new request.
--
-- If @LastEvaluatedStreamArn@ is empty, then the \"last page\" of results
-- has been processed and there is no more data to be retrieved.
--
-- If @LastEvaluatedStreamArn@ is not empty, it does not necessarily mean
-- that there is more data in the result set. The only way to know when you
-- have reached the end of the result set is when @LastEvaluatedStreamArn@
-- is empty.
listStreamsResponse_lastEvaluatedStreamArn :: Lens.Lens' ListStreamsResponse (Prelude.Maybe Prelude.Text)
listStreamsResponse_lastEvaluatedStreamArn :: Lens' ListStreamsResponse (Maybe Text)
listStreamsResponse_lastEvaluatedStreamArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamsResponse' {Maybe Text
lastEvaluatedStreamArn :: Maybe Text
$sel:lastEvaluatedStreamArn:ListStreamsResponse' :: ListStreamsResponse -> Maybe Text
lastEvaluatedStreamArn} -> Maybe Text
lastEvaluatedStreamArn) (\s :: ListStreamsResponse
s@ListStreamsResponse' {} Maybe Text
a -> ListStreamsResponse
s {$sel:lastEvaluatedStreamArn:ListStreamsResponse' :: Maybe Text
lastEvaluatedStreamArn = Maybe Text
a} :: ListStreamsResponse)

-- | A list of stream descriptors associated with the current account and
-- endpoint.
listStreamsResponse_streams :: Lens.Lens' ListStreamsResponse (Prelude.Maybe [Stream])
listStreamsResponse_streams :: Lens' ListStreamsResponse (Maybe [Stream])
listStreamsResponse_streams = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamsResponse' {Maybe [Stream]
streams :: Maybe [Stream]
$sel:streams:ListStreamsResponse' :: ListStreamsResponse -> Maybe [Stream]
streams} -> Maybe [Stream]
streams) (\s :: ListStreamsResponse
s@ListStreamsResponse' {} Maybe [Stream]
a -> ListStreamsResponse
s {$sel:streams:ListStreamsResponse' :: Maybe [Stream]
streams = Maybe [Stream]
a} :: ListStreamsResponse) 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.
listStreamsResponse_httpStatus :: Lens.Lens' ListStreamsResponse Prelude.Int
listStreamsResponse_httpStatus :: Lens' ListStreamsResponse Int
listStreamsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListStreamsResponse' :: ListStreamsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListStreamsResponse
s@ListStreamsResponse' {} Int
a -> ListStreamsResponse
s {$sel:httpStatus:ListStreamsResponse' :: Int
httpStatus = Int
a} :: ListStreamsResponse)

instance Prelude.NFData ListStreamsResponse where
  rnf :: ListStreamsResponse -> ()
rnf ListStreamsResponse' {Int
Maybe [Stream]
Maybe Text
httpStatus :: Int
streams :: Maybe [Stream]
lastEvaluatedStreamArn :: Maybe Text
$sel:httpStatus:ListStreamsResponse' :: ListStreamsResponse -> Int
$sel:streams:ListStreamsResponse' :: ListStreamsResponse -> Maybe [Stream]
$sel:lastEvaluatedStreamArn:ListStreamsResponse' :: ListStreamsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastEvaluatedStreamArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Stream]
streams
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus