{-# 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.SNS.ListTopics
-- 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 a list of the requester\'s topics. Each call returns a limited
-- list of topics, up to 100. If there are more topics, a @NextToken@ is
-- also returned. Use the @NextToken@ parameter in a new @ListTopics@ call
-- to get further results.
--
-- This action is throttled at 30 transactions per second (TPS).
--
-- This operation returns paginated results.
module Amazonka.SNS.ListTopics
  ( -- * Creating a Request
    ListTopics (..),
    newListTopics,

    -- * Request Lenses
    listTopics_nextToken,

    -- * Destructuring the Response
    ListTopicsResponse (..),
    newListTopicsResponse,

    -- * Response Lenses
    listTopicsResponse_nextToken,
    listTopicsResponse_topics,
    listTopicsResponse_httpStatus,
  )
where

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
import Amazonka.SNS.Types

-- | /See:/ 'newListTopics' smart constructor.
data ListTopics = ListTopics'
  { -- | Token returned by the previous @ListTopics@ request.
    ListTopics -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListTopics -> ListTopics -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTopics -> ListTopics -> Bool
$c/= :: ListTopics -> ListTopics -> Bool
== :: ListTopics -> ListTopics -> Bool
$c== :: ListTopics -> ListTopics -> Bool
Prelude.Eq, ReadPrec [ListTopics]
ReadPrec ListTopics
Int -> ReadS ListTopics
ReadS [ListTopics]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTopics]
$creadListPrec :: ReadPrec [ListTopics]
readPrec :: ReadPrec ListTopics
$creadPrec :: ReadPrec ListTopics
readList :: ReadS [ListTopics]
$creadList :: ReadS [ListTopics]
readsPrec :: Int -> ReadS ListTopics
$creadsPrec :: Int -> ReadS ListTopics
Prelude.Read, Int -> ListTopics -> ShowS
[ListTopics] -> ShowS
ListTopics -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTopics] -> ShowS
$cshowList :: [ListTopics] -> ShowS
show :: ListTopics -> String
$cshow :: ListTopics -> String
showsPrec :: Int -> ListTopics -> ShowS
$cshowsPrec :: Int -> ListTopics -> ShowS
Prelude.Show, forall x. Rep ListTopics x -> ListTopics
forall x. ListTopics -> Rep ListTopics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTopics x -> ListTopics
$cfrom :: forall x. ListTopics -> Rep ListTopics x
Prelude.Generic)

-- |
-- Create a value of 'ListTopics' 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:
--
-- 'nextToken', 'listTopics_nextToken' - Token returned by the previous @ListTopics@ request.
newListTopics ::
  ListTopics
newListTopics :: ListTopics
newListTopics =
  ListTopics' {$sel:nextToken:ListTopics' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing}

-- | Token returned by the previous @ListTopics@ request.
listTopics_nextToken :: Lens.Lens' ListTopics (Prelude.Maybe Prelude.Text)
listTopics_nextToken :: Lens' ListTopics (Maybe Text)
listTopics_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTopics' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTopics' :: ListTopics -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTopics
s@ListTopics' {} Maybe Text
a -> ListTopics
s {$sel:nextToken:ListTopics' :: Maybe Text
nextToken = Maybe Text
a} :: ListTopics)

instance Core.AWSPager ListTopics where
  page :: ListTopics -> AWSResponse ListTopics -> Maybe ListTopics
page ListTopics
rq AWSResponse ListTopics
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListTopics
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTopicsResponse (Maybe Text)
listTopicsResponse_nextToken
            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 ListTopics
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTopicsResponse (Maybe [Topic])
listTopicsResponse_topics
            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.$ ListTopics
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListTopics (Maybe Text)
listTopics_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListTopics
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTopicsResponse (Maybe Text)
listTopicsResponse_nextToken
          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 ListTopics where
  type AWSResponse ListTopics = ListTopicsResponse
  request :: (Service -> Service) -> ListTopics -> Request ListTopics
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListTopics
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListTopics)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"ListTopicsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text -> Maybe [Topic] -> Int -> ListTopicsResponse
ListTopicsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Topics"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            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 ListTopics where
  hashWithSalt :: Int -> ListTopics -> Int
hashWithSalt Int
_salt ListTopics' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTopics' :: ListTopics -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

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

instance Data.ToHeaders ListTopics where
  toHeaders :: ListTopics -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery ListTopics where
  toQuery :: ListTopics -> QueryString
toQuery ListTopics' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTopics' :: ListTopics -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ListTopics" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-03-31" :: Prelude.ByteString),
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | Response for ListTopics action.
--
-- /See:/ 'newListTopicsResponse' smart constructor.
data ListTopicsResponse = ListTopicsResponse'
  { -- | Token to pass along to the next @ListTopics@ request. This element is
    -- returned if there are additional topics to retrieve.
    ListTopicsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of topic ARNs.
    ListTopicsResponse -> Maybe [Topic]
topics :: Prelude.Maybe [Topic],
    -- | The response's http status code.
    ListTopicsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListTopicsResponse -> ListTopicsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTopicsResponse -> ListTopicsResponse -> Bool
$c/= :: ListTopicsResponse -> ListTopicsResponse -> Bool
== :: ListTopicsResponse -> ListTopicsResponse -> Bool
$c== :: ListTopicsResponse -> ListTopicsResponse -> Bool
Prelude.Eq, ReadPrec [ListTopicsResponse]
ReadPrec ListTopicsResponse
Int -> ReadS ListTopicsResponse
ReadS [ListTopicsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTopicsResponse]
$creadListPrec :: ReadPrec [ListTopicsResponse]
readPrec :: ReadPrec ListTopicsResponse
$creadPrec :: ReadPrec ListTopicsResponse
readList :: ReadS [ListTopicsResponse]
$creadList :: ReadS [ListTopicsResponse]
readsPrec :: Int -> ReadS ListTopicsResponse
$creadsPrec :: Int -> ReadS ListTopicsResponse
Prelude.Read, Int -> ListTopicsResponse -> ShowS
[ListTopicsResponse] -> ShowS
ListTopicsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTopicsResponse] -> ShowS
$cshowList :: [ListTopicsResponse] -> ShowS
show :: ListTopicsResponse -> String
$cshow :: ListTopicsResponse -> String
showsPrec :: Int -> ListTopicsResponse -> ShowS
$cshowsPrec :: Int -> ListTopicsResponse -> ShowS
Prelude.Show, forall x. Rep ListTopicsResponse x -> ListTopicsResponse
forall x. ListTopicsResponse -> Rep ListTopicsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTopicsResponse x -> ListTopicsResponse
$cfrom :: forall x. ListTopicsResponse -> Rep ListTopicsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListTopicsResponse' 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:
--
-- 'nextToken', 'listTopicsResponse_nextToken' - Token to pass along to the next @ListTopics@ request. This element is
-- returned if there are additional topics to retrieve.
--
-- 'topics', 'listTopicsResponse_topics' - A list of topic ARNs.
--
-- 'httpStatus', 'listTopicsResponse_httpStatus' - The response's http status code.
newListTopicsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListTopicsResponse
newListTopicsResponse :: Int -> ListTopicsResponse
newListTopicsResponse Int
pHttpStatus_ =
  ListTopicsResponse'
    { $sel:nextToken:ListTopicsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:topics:ListTopicsResponse' :: Maybe [Topic]
topics = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListTopicsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Token to pass along to the next @ListTopics@ request. This element is
-- returned if there are additional topics to retrieve.
listTopicsResponse_nextToken :: Lens.Lens' ListTopicsResponse (Prelude.Maybe Prelude.Text)
listTopicsResponse_nextToken :: Lens' ListTopicsResponse (Maybe Text)
listTopicsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTopicsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTopicsResponse' :: ListTopicsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTopicsResponse
s@ListTopicsResponse' {} Maybe Text
a -> ListTopicsResponse
s {$sel:nextToken:ListTopicsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListTopicsResponse)

-- | A list of topic ARNs.
listTopicsResponse_topics :: Lens.Lens' ListTopicsResponse (Prelude.Maybe [Topic])
listTopicsResponse_topics :: Lens' ListTopicsResponse (Maybe [Topic])
listTopicsResponse_topics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTopicsResponse' {Maybe [Topic]
topics :: Maybe [Topic]
$sel:topics:ListTopicsResponse' :: ListTopicsResponse -> Maybe [Topic]
topics} -> Maybe [Topic]
topics) (\s :: ListTopicsResponse
s@ListTopicsResponse' {} Maybe [Topic]
a -> ListTopicsResponse
s {$sel:topics:ListTopicsResponse' :: Maybe [Topic]
topics = Maybe [Topic]
a} :: ListTopicsResponse) 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.
listTopicsResponse_httpStatus :: Lens.Lens' ListTopicsResponse Prelude.Int
listTopicsResponse_httpStatus :: Lens' ListTopicsResponse Int
listTopicsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTopicsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListTopicsResponse' :: ListTopicsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListTopicsResponse
s@ListTopicsResponse' {} Int
a -> ListTopicsResponse
s {$sel:httpStatus:ListTopicsResponse' :: Int
httpStatus = Int
a} :: ListTopicsResponse)

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