{-# 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.AutoScaling.DescribeNotificationConfigurations
-- 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 information about the Amazon SNS notifications that are configured
-- for one or more Auto Scaling groups.
--
-- This operation returns paginated results.
module Amazonka.AutoScaling.DescribeNotificationConfigurations
  ( -- * Creating a Request
    DescribeNotificationConfigurations (..),
    newDescribeNotificationConfigurations,

    -- * Request Lenses
    describeNotificationConfigurations_autoScalingGroupNames,
    describeNotificationConfigurations_maxRecords,
    describeNotificationConfigurations_nextToken,

    -- * Destructuring the Response
    DescribeNotificationConfigurationsResponse (..),
    newDescribeNotificationConfigurationsResponse,

    -- * Response Lenses
    describeNotificationConfigurationsResponse_nextToken,
    describeNotificationConfigurationsResponse_httpStatus,
    describeNotificationConfigurationsResponse_notificationConfigurations,
  )
where

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

-- | /See:/ 'newDescribeNotificationConfigurations' smart constructor.
data DescribeNotificationConfigurations = DescribeNotificationConfigurations'
  { -- | The name of the Auto Scaling group.
    DescribeNotificationConfigurations -> Maybe [Text]
autoScalingGroupNames :: Prelude.Maybe [Prelude.Text],
    -- | The maximum number of items to return with this call. The default value
    -- is @50@ and the maximum value is @100@.
    DescribeNotificationConfigurations -> Maybe Int
maxRecords :: Prelude.Maybe Prelude.Int,
    -- | The token for the next set of items to return. (You received this token
    -- from a previous call.)
    DescribeNotificationConfigurations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeNotificationConfigurations
-> DescribeNotificationConfigurations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeNotificationConfigurations
-> DescribeNotificationConfigurations -> Bool
$c/= :: DescribeNotificationConfigurations
-> DescribeNotificationConfigurations -> Bool
== :: DescribeNotificationConfigurations
-> DescribeNotificationConfigurations -> Bool
$c== :: DescribeNotificationConfigurations
-> DescribeNotificationConfigurations -> Bool
Prelude.Eq, ReadPrec [DescribeNotificationConfigurations]
ReadPrec DescribeNotificationConfigurations
Int -> ReadS DescribeNotificationConfigurations
ReadS [DescribeNotificationConfigurations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeNotificationConfigurations]
$creadListPrec :: ReadPrec [DescribeNotificationConfigurations]
readPrec :: ReadPrec DescribeNotificationConfigurations
$creadPrec :: ReadPrec DescribeNotificationConfigurations
readList :: ReadS [DescribeNotificationConfigurations]
$creadList :: ReadS [DescribeNotificationConfigurations]
readsPrec :: Int -> ReadS DescribeNotificationConfigurations
$creadsPrec :: Int -> ReadS DescribeNotificationConfigurations
Prelude.Read, Int -> DescribeNotificationConfigurations -> ShowS
[DescribeNotificationConfigurations] -> ShowS
DescribeNotificationConfigurations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeNotificationConfigurations] -> ShowS
$cshowList :: [DescribeNotificationConfigurations] -> ShowS
show :: DescribeNotificationConfigurations -> String
$cshow :: DescribeNotificationConfigurations -> String
showsPrec :: Int -> DescribeNotificationConfigurations -> ShowS
$cshowsPrec :: Int -> DescribeNotificationConfigurations -> ShowS
Prelude.Show, forall x.
Rep DescribeNotificationConfigurations x
-> DescribeNotificationConfigurations
forall x.
DescribeNotificationConfigurations
-> Rep DescribeNotificationConfigurations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeNotificationConfigurations x
-> DescribeNotificationConfigurations
$cfrom :: forall x.
DescribeNotificationConfigurations
-> Rep DescribeNotificationConfigurations x
Prelude.Generic)

-- |
-- Create a value of 'DescribeNotificationConfigurations' 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:
--
-- 'autoScalingGroupNames', 'describeNotificationConfigurations_autoScalingGroupNames' - The name of the Auto Scaling group.
--
-- 'maxRecords', 'describeNotificationConfigurations_maxRecords' - The maximum number of items to return with this call. The default value
-- is @50@ and the maximum value is @100@.
--
-- 'nextToken', 'describeNotificationConfigurations_nextToken' - The token for the next set of items to return. (You received this token
-- from a previous call.)
newDescribeNotificationConfigurations ::
  DescribeNotificationConfigurations
newDescribeNotificationConfigurations :: DescribeNotificationConfigurations
newDescribeNotificationConfigurations =
  DescribeNotificationConfigurations'
    { $sel:autoScalingGroupNames:DescribeNotificationConfigurations' :: Maybe [Text]
autoScalingGroupNames =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxRecords:DescribeNotificationConfigurations' :: Maybe Int
maxRecords = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeNotificationConfigurations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The name of the Auto Scaling group.
describeNotificationConfigurations_autoScalingGroupNames :: Lens.Lens' DescribeNotificationConfigurations (Prelude.Maybe [Prelude.Text])
describeNotificationConfigurations_autoScalingGroupNames :: Lens' DescribeNotificationConfigurations (Maybe [Text])
describeNotificationConfigurations_autoScalingGroupNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotificationConfigurations' {Maybe [Text]
autoScalingGroupNames :: Maybe [Text]
$sel:autoScalingGroupNames:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe [Text]
autoScalingGroupNames} -> Maybe [Text]
autoScalingGroupNames) (\s :: DescribeNotificationConfigurations
s@DescribeNotificationConfigurations' {} Maybe [Text]
a -> DescribeNotificationConfigurations
s {$sel:autoScalingGroupNames:DescribeNotificationConfigurations' :: Maybe [Text]
autoScalingGroupNames = Maybe [Text]
a} :: DescribeNotificationConfigurations) 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 maximum number of items to return with this call. The default value
-- is @50@ and the maximum value is @100@.
describeNotificationConfigurations_maxRecords :: Lens.Lens' DescribeNotificationConfigurations (Prelude.Maybe Prelude.Int)
describeNotificationConfigurations_maxRecords :: Lens' DescribeNotificationConfigurations (Maybe Int)
describeNotificationConfigurations_maxRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotificationConfigurations' {Maybe Int
maxRecords :: Maybe Int
$sel:maxRecords:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe Int
maxRecords} -> Maybe Int
maxRecords) (\s :: DescribeNotificationConfigurations
s@DescribeNotificationConfigurations' {} Maybe Int
a -> DescribeNotificationConfigurations
s {$sel:maxRecords:DescribeNotificationConfigurations' :: Maybe Int
maxRecords = Maybe Int
a} :: DescribeNotificationConfigurations)

-- | The token for the next set of items to return. (You received this token
-- from a previous call.)
describeNotificationConfigurations_nextToken :: Lens.Lens' DescribeNotificationConfigurations (Prelude.Maybe Prelude.Text)
describeNotificationConfigurations_nextToken :: Lens' DescribeNotificationConfigurations (Maybe Text)
describeNotificationConfigurations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotificationConfigurations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeNotificationConfigurations
s@DescribeNotificationConfigurations' {} Maybe Text
a -> DescribeNotificationConfigurations
s {$sel:nextToken:DescribeNotificationConfigurations' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeNotificationConfigurations)

instance
  Core.AWSPager
    DescribeNotificationConfigurations
  where
  page :: DescribeNotificationConfigurations
-> AWSResponse DescribeNotificationConfigurations
-> Maybe DescribeNotificationConfigurations
page DescribeNotificationConfigurations
rq AWSResponse DescribeNotificationConfigurations
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeNotificationConfigurations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeNotificationConfigurationsResponse (Maybe Text)
describeNotificationConfigurationsResponse_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 DescribeNotificationConfigurations
rs
            forall s a. s -> Getting a s a -> a
Lens.^. Lens'
  DescribeNotificationConfigurationsResponse
  [NotificationConfiguration]
describeNotificationConfigurationsResponse_notificationConfigurations
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ DescribeNotificationConfigurations
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeNotificationConfigurations (Maybe Text)
describeNotificationConfigurations_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeNotificationConfigurations
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeNotificationConfigurationsResponse (Maybe Text)
describeNotificationConfigurationsResponse_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
    DescribeNotificationConfigurations
  where
  type
    AWSResponse DescribeNotificationConfigurations =
      DescribeNotificationConfigurationsResponse
  request :: (Service -> Service)
-> DescribeNotificationConfigurations
-> Request DescribeNotificationConfigurations
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 DescribeNotificationConfigurations
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeNotificationConfigurations)))
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
"DescribeNotificationConfigurationsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Int
-> [NotificationConfiguration]
-> DescribeNotificationConfigurationsResponse
DescribeNotificationConfigurationsResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            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
"NotificationConfigurations"
                            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 a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member"
                        )
      )

instance
  Prelude.Hashable
    DescribeNotificationConfigurations
  where
  hashWithSalt :: Int -> DescribeNotificationConfigurations -> Int
hashWithSalt
    Int
_salt
    DescribeNotificationConfigurations' {Maybe Int
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
maxRecords :: Maybe Int
autoScalingGroupNames :: Maybe [Text]
$sel:nextToken:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe Text
$sel:maxRecords:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe Int
$sel:autoScalingGroupNames:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe [Text]
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
autoScalingGroupNames
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxRecords
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance
  Prelude.NFData
    DescribeNotificationConfigurations
  where
  rnf :: DescribeNotificationConfigurations -> ()
rnf DescribeNotificationConfigurations' {Maybe Int
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
maxRecords :: Maybe Int
autoScalingGroupNames :: Maybe [Text]
$sel:nextToken:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe Text
$sel:maxRecords:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe Int
$sel:autoScalingGroupNames:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
autoScalingGroupNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxRecords
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

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

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

instance
  Data.ToQuery
    DescribeNotificationConfigurations
  where
  toQuery :: DescribeNotificationConfigurations -> QueryString
toQuery DescribeNotificationConfigurations' {Maybe Int
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
maxRecords :: Maybe Int
autoScalingGroupNames :: Maybe [Text]
$sel:nextToken:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe Text
$sel:maxRecords:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe Int
$sel:autoScalingGroupNames:DescribeNotificationConfigurations' :: DescribeNotificationConfigurations -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DescribeNotificationConfigurations" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-01-01" :: Prelude.ByteString),
        ByteString
"AutoScalingGroupNames"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
autoScalingGroupNames
            ),
        ByteString
"MaxRecords" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxRecords,
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newDescribeNotificationConfigurationsResponse' smart constructor.
data DescribeNotificationConfigurationsResponse = DescribeNotificationConfigurationsResponse'
  { -- | A string that indicates that the response contains more items than can
    -- be returned in a single response. To receive additional items, specify
    -- this string for the @NextToken@ value when requesting the next set of
    -- items. This value is null when there are no more items to return.
    DescribeNotificationConfigurationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeNotificationConfigurationsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The notification configurations.
    DescribeNotificationConfigurationsResponse
-> [NotificationConfiguration]
notificationConfigurations :: [NotificationConfiguration]
  }
  deriving (DescribeNotificationConfigurationsResponse
-> DescribeNotificationConfigurationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeNotificationConfigurationsResponse
-> DescribeNotificationConfigurationsResponse -> Bool
$c/= :: DescribeNotificationConfigurationsResponse
-> DescribeNotificationConfigurationsResponse -> Bool
== :: DescribeNotificationConfigurationsResponse
-> DescribeNotificationConfigurationsResponse -> Bool
$c== :: DescribeNotificationConfigurationsResponse
-> DescribeNotificationConfigurationsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeNotificationConfigurationsResponse]
ReadPrec DescribeNotificationConfigurationsResponse
Int -> ReadS DescribeNotificationConfigurationsResponse
ReadS [DescribeNotificationConfigurationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeNotificationConfigurationsResponse]
$creadListPrec :: ReadPrec [DescribeNotificationConfigurationsResponse]
readPrec :: ReadPrec DescribeNotificationConfigurationsResponse
$creadPrec :: ReadPrec DescribeNotificationConfigurationsResponse
readList :: ReadS [DescribeNotificationConfigurationsResponse]
$creadList :: ReadS [DescribeNotificationConfigurationsResponse]
readsPrec :: Int -> ReadS DescribeNotificationConfigurationsResponse
$creadsPrec :: Int -> ReadS DescribeNotificationConfigurationsResponse
Prelude.Read, Int -> DescribeNotificationConfigurationsResponse -> ShowS
[DescribeNotificationConfigurationsResponse] -> ShowS
DescribeNotificationConfigurationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeNotificationConfigurationsResponse] -> ShowS
$cshowList :: [DescribeNotificationConfigurationsResponse] -> ShowS
show :: DescribeNotificationConfigurationsResponse -> String
$cshow :: DescribeNotificationConfigurationsResponse -> String
showsPrec :: Int -> DescribeNotificationConfigurationsResponse -> ShowS
$cshowsPrec :: Int -> DescribeNotificationConfigurationsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeNotificationConfigurationsResponse x
-> DescribeNotificationConfigurationsResponse
forall x.
DescribeNotificationConfigurationsResponse
-> Rep DescribeNotificationConfigurationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeNotificationConfigurationsResponse x
-> DescribeNotificationConfigurationsResponse
$cfrom :: forall x.
DescribeNotificationConfigurationsResponse
-> Rep DescribeNotificationConfigurationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeNotificationConfigurationsResponse' 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', 'describeNotificationConfigurationsResponse_nextToken' - A string that indicates that the response contains more items than can
-- be returned in a single response. To receive additional items, specify
-- this string for the @NextToken@ value when requesting the next set of
-- items. This value is null when there are no more items to return.
--
-- 'httpStatus', 'describeNotificationConfigurationsResponse_httpStatus' - The response's http status code.
--
-- 'notificationConfigurations', 'describeNotificationConfigurationsResponse_notificationConfigurations' - The notification configurations.
newDescribeNotificationConfigurationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeNotificationConfigurationsResponse
newDescribeNotificationConfigurationsResponse :: Int -> DescribeNotificationConfigurationsResponse
newDescribeNotificationConfigurationsResponse
  Int
pHttpStatus_ =
    DescribeNotificationConfigurationsResponse'
      { $sel:nextToken:DescribeNotificationConfigurationsResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeNotificationConfigurationsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:notificationConfigurations:DescribeNotificationConfigurationsResponse' :: [NotificationConfiguration]
notificationConfigurations =
          forall a. Monoid a => a
Prelude.mempty
      }

-- | A string that indicates that the response contains more items than can
-- be returned in a single response. To receive additional items, specify
-- this string for the @NextToken@ value when requesting the next set of
-- items. This value is null when there are no more items to return.
describeNotificationConfigurationsResponse_nextToken :: Lens.Lens' DescribeNotificationConfigurationsResponse (Prelude.Maybe Prelude.Text)
describeNotificationConfigurationsResponse_nextToken :: Lens' DescribeNotificationConfigurationsResponse (Maybe Text)
describeNotificationConfigurationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotificationConfigurationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeNotificationConfigurationsResponse' :: DescribeNotificationConfigurationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeNotificationConfigurationsResponse
s@DescribeNotificationConfigurationsResponse' {} Maybe Text
a -> DescribeNotificationConfigurationsResponse
s {$sel:nextToken:DescribeNotificationConfigurationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeNotificationConfigurationsResponse)

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

-- | The notification configurations.
describeNotificationConfigurationsResponse_notificationConfigurations :: Lens.Lens' DescribeNotificationConfigurationsResponse [NotificationConfiguration]
describeNotificationConfigurationsResponse_notificationConfigurations :: Lens'
  DescribeNotificationConfigurationsResponse
  [NotificationConfiguration]
describeNotificationConfigurationsResponse_notificationConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotificationConfigurationsResponse' {[NotificationConfiguration]
notificationConfigurations :: [NotificationConfiguration]
$sel:notificationConfigurations:DescribeNotificationConfigurationsResponse' :: DescribeNotificationConfigurationsResponse
-> [NotificationConfiguration]
notificationConfigurations} -> [NotificationConfiguration]
notificationConfigurations) (\s :: DescribeNotificationConfigurationsResponse
s@DescribeNotificationConfigurationsResponse' {} [NotificationConfiguration]
a -> DescribeNotificationConfigurationsResponse
s {$sel:notificationConfigurations:DescribeNotificationConfigurationsResponse' :: [NotificationConfiguration]
notificationConfigurations = [NotificationConfiguration]
a} :: DescribeNotificationConfigurationsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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