{-# 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.Budgets.DescribeSubscribersForNotification
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the subscribers that are associated with a notification.
--
-- This operation returns paginated results.
module Amazonka.Budgets.DescribeSubscribersForNotification
  ( -- * Creating a Request
    DescribeSubscribersForNotification (..),
    newDescribeSubscribersForNotification,

    -- * Request Lenses
    describeSubscribersForNotification_maxResults,
    describeSubscribersForNotification_nextToken,
    describeSubscribersForNotification_accountId,
    describeSubscribersForNotification_budgetName,
    describeSubscribersForNotification_notification,

    -- * Destructuring the Response
    DescribeSubscribersForNotificationResponse (..),
    newDescribeSubscribersForNotificationResponse,

    -- * Response Lenses
    describeSubscribersForNotificationResponse_nextToken,
    describeSubscribersForNotificationResponse_subscribers,
    describeSubscribersForNotificationResponse_httpStatus,
  )
where

import Amazonka.Budgets.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

-- | Request of DescribeSubscribersForNotification
--
-- /See:/ 'newDescribeSubscribersForNotification' smart constructor.
data DescribeSubscribersForNotification = DescribeSubscribersForNotification'
  { -- | An optional integer that represents how many entries a paginated
    -- response contains. The maximum is 100.
    DescribeSubscribersForNotification -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The pagination token that you include in your request to indicate the
    -- next set of results that you want to retrieve.
    DescribeSubscribersForNotification -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The @accountId@ that is associated with the budget whose subscribers you
    -- want descriptions of.
    DescribeSubscribersForNotification -> Text
accountId :: Prelude.Text,
    -- | The name of the budget whose subscribers you want descriptions of.
    DescribeSubscribersForNotification -> Text
budgetName :: Prelude.Text,
    -- | The notification whose subscribers you want to list.
    DescribeSubscribersForNotification -> Notification
notification :: Notification
  }
  deriving (DescribeSubscribersForNotification
-> DescribeSubscribersForNotification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSubscribersForNotification
-> DescribeSubscribersForNotification -> Bool
$c/= :: DescribeSubscribersForNotification
-> DescribeSubscribersForNotification -> Bool
== :: DescribeSubscribersForNotification
-> DescribeSubscribersForNotification -> Bool
$c== :: DescribeSubscribersForNotification
-> DescribeSubscribersForNotification -> Bool
Prelude.Eq, ReadPrec [DescribeSubscribersForNotification]
ReadPrec DescribeSubscribersForNotification
Int -> ReadS DescribeSubscribersForNotification
ReadS [DescribeSubscribersForNotification]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSubscribersForNotification]
$creadListPrec :: ReadPrec [DescribeSubscribersForNotification]
readPrec :: ReadPrec DescribeSubscribersForNotification
$creadPrec :: ReadPrec DescribeSubscribersForNotification
readList :: ReadS [DescribeSubscribersForNotification]
$creadList :: ReadS [DescribeSubscribersForNotification]
readsPrec :: Int -> ReadS DescribeSubscribersForNotification
$creadsPrec :: Int -> ReadS DescribeSubscribersForNotification
Prelude.Read, Int -> DescribeSubscribersForNotification -> ShowS
[DescribeSubscribersForNotification] -> ShowS
DescribeSubscribersForNotification -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSubscribersForNotification] -> ShowS
$cshowList :: [DescribeSubscribersForNotification] -> ShowS
show :: DescribeSubscribersForNotification -> String
$cshow :: DescribeSubscribersForNotification -> String
showsPrec :: Int -> DescribeSubscribersForNotification -> ShowS
$cshowsPrec :: Int -> DescribeSubscribersForNotification -> ShowS
Prelude.Show, forall x.
Rep DescribeSubscribersForNotification x
-> DescribeSubscribersForNotification
forall x.
DescribeSubscribersForNotification
-> Rep DescribeSubscribersForNotification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSubscribersForNotification x
-> DescribeSubscribersForNotification
$cfrom :: forall x.
DescribeSubscribersForNotification
-> Rep DescribeSubscribersForNotification x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSubscribersForNotification' 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:
--
-- 'maxResults', 'describeSubscribersForNotification_maxResults' - An optional integer that represents how many entries a paginated
-- response contains. The maximum is 100.
--
-- 'nextToken', 'describeSubscribersForNotification_nextToken' - The pagination token that you include in your request to indicate the
-- next set of results that you want to retrieve.
--
-- 'accountId', 'describeSubscribersForNotification_accountId' - The @accountId@ that is associated with the budget whose subscribers you
-- want descriptions of.
--
-- 'budgetName', 'describeSubscribersForNotification_budgetName' - The name of the budget whose subscribers you want descriptions of.
--
-- 'notification', 'describeSubscribersForNotification_notification' - The notification whose subscribers you want to list.
newDescribeSubscribersForNotification ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'budgetName'
  Prelude.Text ->
  -- | 'notification'
  Notification ->
  DescribeSubscribersForNotification
newDescribeSubscribersForNotification :: Text -> Text -> Notification -> DescribeSubscribersForNotification
newDescribeSubscribersForNotification
  Text
pAccountId_
  Text
pBudgetName_
  Notification
pNotification_ =
    DescribeSubscribersForNotification'
      { $sel:maxResults:DescribeSubscribersForNotification' :: Maybe Natural
maxResults =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:DescribeSubscribersForNotification' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:accountId:DescribeSubscribersForNotification' :: Text
accountId = Text
pAccountId_,
        $sel:budgetName:DescribeSubscribersForNotification' :: Text
budgetName = Text
pBudgetName_,
        $sel:notification:DescribeSubscribersForNotification' :: Notification
notification = Notification
pNotification_
      }

-- | An optional integer that represents how many entries a paginated
-- response contains. The maximum is 100.
describeSubscribersForNotification_maxResults :: Lens.Lens' DescribeSubscribersForNotification (Prelude.Maybe Prelude.Natural)
describeSubscribersForNotification_maxResults :: Lens' DescribeSubscribersForNotification (Maybe Natural)
describeSubscribersForNotification_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSubscribersForNotification' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: DescribeSubscribersForNotification
s@DescribeSubscribersForNotification' {} Maybe Natural
a -> DescribeSubscribersForNotification
s {$sel:maxResults:DescribeSubscribersForNotification' :: Maybe Natural
maxResults = Maybe Natural
a} :: DescribeSubscribersForNotification)

-- | The pagination token that you include in your request to indicate the
-- next set of results that you want to retrieve.
describeSubscribersForNotification_nextToken :: Lens.Lens' DescribeSubscribersForNotification (Prelude.Maybe Prelude.Text)
describeSubscribersForNotification_nextToken :: Lens' DescribeSubscribersForNotification (Maybe Text)
describeSubscribersForNotification_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSubscribersForNotification' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeSubscribersForNotification
s@DescribeSubscribersForNotification' {} Maybe Text
a -> DescribeSubscribersForNotification
s {$sel:nextToken:DescribeSubscribersForNotification' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeSubscribersForNotification)

-- | The @accountId@ that is associated with the budget whose subscribers you
-- want descriptions of.
describeSubscribersForNotification_accountId :: Lens.Lens' DescribeSubscribersForNotification Prelude.Text
describeSubscribersForNotification_accountId :: Lens' DescribeSubscribersForNotification Text
describeSubscribersForNotification_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSubscribersForNotification' {Text
accountId :: Text
$sel:accountId:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Text
accountId} -> Text
accountId) (\s :: DescribeSubscribersForNotification
s@DescribeSubscribersForNotification' {} Text
a -> DescribeSubscribersForNotification
s {$sel:accountId:DescribeSubscribersForNotification' :: Text
accountId = Text
a} :: DescribeSubscribersForNotification)

-- | The name of the budget whose subscribers you want descriptions of.
describeSubscribersForNotification_budgetName :: Lens.Lens' DescribeSubscribersForNotification Prelude.Text
describeSubscribersForNotification_budgetName :: Lens' DescribeSubscribersForNotification Text
describeSubscribersForNotification_budgetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSubscribersForNotification' {Text
budgetName :: Text
$sel:budgetName:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Text
budgetName} -> Text
budgetName) (\s :: DescribeSubscribersForNotification
s@DescribeSubscribersForNotification' {} Text
a -> DescribeSubscribersForNotification
s {$sel:budgetName:DescribeSubscribersForNotification' :: Text
budgetName = Text
a} :: DescribeSubscribersForNotification)

-- | The notification whose subscribers you want to list.
describeSubscribersForNotification_notification :: Lens.Lens' DescribeSubscribersForNotification Notification
describeSubscribersForNotification_notification :: Lens' DescribeSubscribersForNotification Notification
describeSubscribersForNotification_notification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSubscribersForNotification' {Notification
notification :: Notification
$sel:notification:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Notification
notification} -> Notification
notification) (\s :: DescribeSubscribersForNotification
s@DescribeSubscribersForNotification' {} Notification
a -> DescribeSubscribersForNotification
s {$sel:notification:DescribeSubscribersForNotification' :: Notification
notification = Notification
a} :: DescribeSubscribersForNotification)

instance
  Core.AWSPager
    DescribeSubscribersForNotification
  where
  page :: DescribeSubscribersForNotification
-> AWSResponse DescribeSubscribersForNotification
-> Maybe DescribeSubscribersForNotification
page DescribeSubscribersForNotification
rq AWSResponse DescribeSubscribersForNotification
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeSubscribersForNotification
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeSubscribersForNotificationResponse (Maybe Text)
describeSubscribersForNotificationResponse_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 DescribeSubscribersForNotification
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  DescribeSubscribersForNotificationResponse
  (Maybe (NonEmpty Subscriber))
describeSubscribersForNotificationResponse_subscribers
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to forall l. IsList l => l -> [Item l]
Prelude.toList
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ DescribeSubscribersForNotification
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeSubscribersForNotification (Maybe Text)
describeSubscribersForNotification_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeSubscribersForNotification
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeSubscribersForNotificationResponse (Maybe Text)
describeSubscribersForNotificationResponse_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
    DescribeSubscribersForNotification
  where
  type
    AWSResponse DescribeSubscribersForNotification =
      DescribeSubscribersForNotificationResponse
  request :: (Service -> Service)
-> DescribeSubscribersForNotification
-> Request DescribeSubscribersForNotification
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 DescribeSubscribersForNotification
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeSubscribersForNotification)))
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 (NonEmpty Subscriber)
-> Int
-> DescribeSubscribersForNotificationResponse
DescribeSubscribersForNotificationResponse'
            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
"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
"Subscribers")
            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
    DescribeSubscribersForNotification
  where
  hashWithSalt :: Int -> DescribeSubscribersForNotification -> Int
hashWithSalt
    Int
_salt
    DescribeSubscribersForNotification' {Maybe Natural
Maybe Text
Text
Notification
notification :: Notification
budgetName :: Text
accountId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:notification:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Notification
$sel:budgetName:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Text
$sel:accountId:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Text
$sel:nextToken:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Maybe Text
$sel:maxResults:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Maybe Natural
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
budgetName
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Notification
notification

instance
  Prelude.NFData
    DescribeSubscribersForNotification
  where
  rnf :: DescribeSubscribersForNotification -> ()
rnf DescribeSubscribersForNotification' {Maybe Natural
Maybe Text
Text
Notification
notification :: Notification
budgetName :: Text
accountId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:notification:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Notification
$sel:budgetName:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Text
$sel:accountId:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Text
$sel:nextToken:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Maybe Text
$sel:maxResults:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
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 Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
budgetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Notification
notification

instance
  Data.ToHeaders
    DescribeSubscribersForNotification
  where
  toHeaders :: DescribeSubscribersForNotification -> 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
"AWSBudgetServiceGateway.DescribeSubscribersForNotification" ::
                          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
    DescribeSubscribersForNotification
  where
  toJSON :: DescribeSubscribersForNotification -> Value
toJSON DescribeSubscribersForNotification' {Maybe Natural
Maybe Text
Text
Notification
notification :: Notification
budgetName :: Text
accountId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:notification:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Notification
$sel:budgetName:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Text
$sel:accountId:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Text
$sel:nextToken:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Maybe Text
$sel:maxResults:DescribeSubscribersForNotification' :: DescribeSubscribersForNotification -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaxResults" 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
maxResults,
            (Key
"NextToken" 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
nextToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"AccountId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
accountId),
            forall a. a -> Maybe a
Prelude.Just (Key
"BudgetName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
budgetName),
            forall a. a -> Maybe a
Prelude.Just (Key
"Notification" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Notification
notification)
          ]
      )

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

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

-- | Response of DescribeSubscribersForNotification
--
-- /See:/ 'newDescribeSubscribersForNotificationResponse' smart constructor.
data DescribeSubscribersForNotificationResponse = DescribeSubscribersForNotificationResponse'
  { -- | The pagination token in the service response that indicates the next set
    -- of results that you can retrieve.
    DescribeSubscribersForNotificationResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of subscribers that are associated with a notification.
    DescribeSubscribersForNotificationResponse
-> Maybe (NonEmpty Subscriber)
subscribers :: Prelude.Maybe (Prelude.NonEmpty Subscriber),
    -- | The response's http status code.
    DescribeSubscribersForNotificationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeSubscribersForNotificationResponse
-> DescribeSubscribersForNotificationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSubscribersForNotificationResponse
-> DescribeSubscribersForNotificationResponse -> Bool
$c/= :: DescribeSubscribersForNotificationResponse
-> DescribeSubscribersForNotificationResponse -> Bool
== :: DescribeSubscribersForNotificationResponse
-> DescribeSubscribersForNotificationResponse -> Bool
$c== :: DescribeSubscribersForNotificationResponse
-> DescribeSubscribersForNotificationResponse -> Bool
Prelude.Eq, Int -> DescribeSubscribersForNotificationResponse -> ShowS
[DescribeSubscribersForNotificationResponse] -> ShowS
DescribeSubscribersForNotificationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSubscribersForNotificationResponse] -> ShowS
$cshowList :: [DescribeSubscribersForNotificationResponse] -> ShowS
show :: DescribeSubscribersForNotificationResponse -> String
$cshow :: DescribeSubscribersForNotificationResponse -> String
showsPrec :: Int -> DescribeSubscribersForNotificationResponse -> ShowS
$cshowsPrec :: Int -> DescribeSubscribersForNotificationResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeSubscribersForNotificationResponse x
-> DescribeSubscribersForNotificationResponse
forall x.
DescribeSubscribersForNotificationResponse
-> Rep DescribeSubscribersForNotificationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSubscribersForNotificationResponse x
-> DescribeSubscribersForNotificationResponse
$cfrom :: forall x.
DescribeSubscribersForNotificationResponse
-> Rep DescribeSubscribersForNotificationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSubscribersForNotificationResponse' 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', 'describeSubscribersForNotificationResponse_nextToken' - The pagination token in the service response that indicates the next set
-- of results that you can retrieve.
--
-- 'subscribers', 'describeSubscribersForNotificationResponse_subscribers' - A list of subscribers that are associated with a notification.
--
-- 'httpStatus', 'describeSubscribersForNotificationResponse_httpStatus' - The response's http status code.
newDescribeSubscribersForNotificationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeSubscribersForNotificationResponse
newDescribeSubscribersForNotificationResponse :: Int -> DescribeSubscribersForNotificationResponse
newDescribeSubscribersForNotificationResponse
  Int
pHttpStatus_ =
    DescribeSubscribersForNotificationResponse'
      { $sel:nextToken:DescribeSubscribersForNotificationResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:subscribers:DescribeSubscribersForNotificationResponse' :: Maybe (NonEmpty Subscriber)
subscribers = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeSubscribersForNotificationResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The pagination token in the service response that indicates the next set
-- of results that you can retrieve.
describeSubscribersForNotificationResponse_nextToken :: Lens.Lens' DescribeSubscribersForNotificationResponse (Prelude.Maybe Prelude.Text)
describeSubscribersForNotificationResponse_nextToken :: Lens' DescribeSubscribersForNotificationResponse (Maybe Text)
describeSubscribersForNotificationResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSubscribersForNotificationResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeSubscribersForNotificationResponse' :: DescribeSubscribersForNotificationResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeSubscribersForNotificationResponse
s@DescribeSubscribersForNotificationResponse' {} Maybe Text
a -> DescribeSubscribersForNotificationResponse
s {$sel:nextToken:DescribeSubscribersForNotificationResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeSubscribersForNotificationResponse)

-- | A list of subscribers that are associated with a notification.
describeSubscribersForNotificationResponse_subscribers :: Lens.Lens' DescribeSubscribersForNotificationResponse (Prelude.Maybe (Prelude.NonEmpty Subscriber))
describeSubscribersForNotificationResponse_subscribers :: Lens'
  DescribeSubscribersForNotificationResponse
  (Maybe (NonEmpty Subscriber))
describeSubscribersForNotificationResponse_subscribers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSubscribersForNotificationResponse' {Maybe (NonEmpty Subscriber)
subscribers :: Maybe (NonEmpty Subscriber)
$sel:subscribers:DescribeSubscribersForNotificationResponse' :: DescribeSubscribersForNotificationResponse
-> Maybe (NonEmpty Subscriber)
subscribers} -> Maybe (NonEmpty Subscriber)
subscribers) (\s :: DescribeSubscribersForNotificationResponse
s@DescribeSubscribersForNotificationResponse' {} Maybe (NonEmpty Subscriber)
a -> DescribeSubscribersForNotificationResponse
s {$sel:subscribers:DescribeSubscribersForNotificationResponse' :: Maybe (NonEmpty Subscriber)
subscribers = Maybe (NonEmpty Subscriber)
a} :: DescribeSubscribersForNotificationResponse) 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.
describeSubscribersForNotificationResponse_httpStatus :: Lens.Lens' DescribeSubscribersForNotificationResponse Prelude.Int
describeSubscribersForNotificationResponse_httpStatus :: Lens' DescribeSubscribersForNotificationResponse Int
describeSubscribersForNotificationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSubscribersForNotificationResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeSubscribersForNotificationResponse' :: DescribeSubscribersForNotificationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeSubscribersForNotificationResponse
s@DescribeSubscribersForNotificationResponse' {} Int
a -> DescribeSubscribersForNotificationResponse
s {$sel:httpStatus:DescribeSubscribersForNotificationResponse' :: Int
httpStatus = Int
a} :: DescribeSubscribersForNotificationResponse)

instance
  Prelude.NFData
    DescribeSubscribersForNotificationResponse
  where
  rnf :: DescribeSubscribersForNotificationResponse -> ()
rnf DescribeSubscribersForNotificationResponse' {Int
Maybe (NonEmpty Subscriber)
Maybe Text
httpStatus :: Int
subscribers :: Maybe (NonEmpty Subscriber)
nextToken :: Maybe Text
$sel:httpStatus:DescribeSubscribersForNotificationResponse' :: DescribeSubscribersForNotificationResponse -> Int
$sel:subscribers:DescribeSubscribersForNotificationResponse' :: DescribeSubscribersForNotificationResponse
-> Maybe (NonEmpty Subscriber)
$sel:nextToken:DescribeSubscribersForNotificationResponse' :: DescribeSubscribersForNotificationResponse -> 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 (NonEmpty Subscriber)
subscribers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus