{-# 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 #-}
module Amazonka.WorkDocs.DescribeNotificationSubscriptions
(
DescribeNotificationSubscriptions (..),
newDescribeNotificationSubscriptions,
describeNotificationSubscriptions_limit,
describeNotificationSubscriptions_marker,
describeNotificationSubscriptions_organizationId,
DescribeNotificationSubscriptionsResponse (..),
newDescribeNotificationSubscriptionsResponse,
describeNotificationSubscriptionsResponse_marker,
describeNotificationSubscriptionsResponse_subscriptions,
describeNotificationSubscriptionsResponse_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.WorkDocs.Types
data DescribeNotificationSubscriptions = DescribeNotificationSubscriptions'
{
DescribeNotificationSubscriptions -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
DescribeNotificationSubscriptions -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
DescribeNotificationSubscriptions -> Text
organizationId :: Prelude.Text
}
deriving (DescribeNotificationSubscriptions
-> DescribeNotificationSubscriptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeNotificationSubscriptions
-> DescribeNotificationSubscriptions -> Bool
$c/= :: DescribeNotificationSubscriptions
-> DescribeNotificationSubscriptions -> Bool
== :: DescribeNotificationSubscriptions
-> DescribeNotificationSubscriptions -> Bool
$c== :: DescribeNotificationSubscriptions
-> DescribeNotificationSubscriptions -> Bool
Prelude.Eq, ReadPrec [DescribeNotificationSubscriptions]
ReadPrec DescribeNotificationSubscriptions
Int -> ReadS DescribeNotificationSubscriptions
ReadS [DescribeNotificationSubscriptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeNotificationSubscriptions]
$creadListPrec :: ReadPrec [DescribeNotificationSubscriptions]
readPrec :: ReadPrec DescribeNotificationSubscriptions
$creadPrec :: ReadPrec DescribeNotificationSubscriptions
readList :: ReadS [DescribeNotificationSubscriptions]
$creadList :: ReadS [DescribeNotificationSubscriptions]
readsPrec :: Int -> ReadS DescribeNotificationSubscriptions
$creadsPrec :: Int -> ReadS DescribeNotificationSubscriptions
Prelude.Read, Int -> DescribeNotificationSubscriptions -> ShowS
[DescribeNotificationSubscriptions] -> ShowS
DescribeNotificationSubscriptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeNotificationSubscriptions] -> ShowS
$cshowList :: [DescribeNotificationSubscriptions] -> ShowS
show :: DescribeNotificationSubscriptions -> String
$cshow :: DescribeNotificationSubscriptions -> String
showsPrec :: Int -> DescribeNotificationSubscriptions -> ShowS
$cshowsPrec :: Int -> DescribeNotificationSubscriptions -> ShowS
Prelude.Show, forall x.
Rep DescribeNotificationSubscriptions x
-> DescribeNotificationSubscriptions
forall x.
DescribeNotificationSubscriptions
-> Rep DescribeNotificationSubscriptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeNotificationSubscriptions x
-> DescribeNotificationSubscriptions
$cfrom :: forall x.
DescribeNotificationSubscriptions
-> Rep DescribeNotificationSubscriptions x
Prelude.Generic)
newDescribeNotificationSubscriptions ::
Prelude.Text ->
DescribeNotificationSubscriptions
newDescribeNotificationSubscriptions :: Text -> DescribeNotificationSubscriptions
newDescribeNotificationSubscriptions Text
pOrganizationId_ =
DescribeNotificationSubscriptions'
{ $sel:limit:DescribeNotificationSubscriptions' :: Maybe Natural
limit =
forall a. Maybe a
Prelude.Nothing,
$sel:marker:DescribeNotificationSubscriptions' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
$sel:organizationId:DescribeNotificationSubscriptions' :: Text
organizationId = Text
pOrganizationId_
}
describeNotificationSubscriptions_limit :: Lens.Lens' DescribeNotificationSubscriptions (Prelude.Maybe Prelude.Natural)
describeNotificationSubscriptions_limit :: Lens' DescribeNotificationSubscriptions (Maybe Natural)
describeNotificationSubscriptions_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotificationSubscriptions' {Maybe Natural
limit :: Maybe Natural
$sel:limit:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: DescribeNotificationSubscriptions
s@DescribeNotificationSubscriptions' {} Maybe Natural
a -> DescribeNotificationSubscriptions
s {$sel:limit:DescribeNotificationSubscriptions' :: Maybe Natural
limit = Maybe Natural
a} :: DescribeNotificationSubscriptions)
describeNotificationSubscriptions_marker :: Lens.Lens' DescribeNotificationSubscriptions (Prelude.Maybe Prelude.Text)
describeNotificationSubscriptions_marker :: Lens' DescribeNotificationSubscriptions (Maybe Text)
describeNotificationSubscriptions_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotificationSubscriptions' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeNotificationSubscriptions
s@DescribeNotificationSubscriptions' {} Maybe Text
a -> DescribeNotificationSubscriptions
s {$sel:marker:DescribeNotificationSubscriptions' :: Maybe Text
marker = Maybe Text
a} :: DescribeNotificationSubscriptions)
describeNotificationSubscriptions_organizationId :: Lens.Lens' DescribeNotificationSubscriptions Prelude.Text
describeNotificationSubscriptions_organizationId :: Lens' DescribeNotificationSubscriptions Text
describeNotificationSubscriptions_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotificationSubscriptions' {Text
organizationId :: Text
$sel:organizationId:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Text
organizationId} -> Text
organizationId) (\s :: DescribeNotificationSubscriptions
s@DescribeNotificationSubscriptions' {} Text
a -> DescribeNotificationSubscriptions
s {$sel:organizationId:DescribeNotificationSubscriptions' :: Text
organizationId = Text
a} :: DescribeNotificationSubscriptions)
instance
Core.AWSPager
DescribeNotificationSubscriptions
where
page :: DescribeNotificationSubscriptions
-> AWSResponse DescribeNotificationSubscriptions
-> Maybe DescribeNotificationSubscriptions
page DescribeNotificationSubscriptions
rq AWSResponse DescribeNotificationSubscriptions
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse DescribeNotificationSubscriptions
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeNotificationSubscriptionsResponse (Maybe Text)
describeNotificationSubscriptionsResponse_marker
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 DescribeNotificationSubscriptions
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
DescribeNotificationSubscriptionsResponse (Maybe [Subscription])
describeNotificationSubscriptionsResponse_subscriptions
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.$ DescribeNotificationSubscriptions
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeNotificationSubscriptions (Maybe Text)
describeNotificationSubscriptions_marker
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeNotificationSubscriptions
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeNotificationSubscriptionsResponse (Maybe Text)
describeNotificationSubscriptionsResponse_marker
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
DescribeNotificationSubscriptions
where
type
AWSResponse DescribeNotificationSubscriptions =
DescribeNotificationSubscriptionsResponse
request :: (Service -> Service)
-> DescribeNotificationSubscriptions
-> Request DescribeNotificationSubscriptions
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeNotificationSubscriptions
-> ClientResponse ClientBody
-> m (Either
Error
(ClientResponse (AWSResponse DescribeNotificationSubscriptions)))
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 [Subscription]
-> Int
-> DescribeNotificationSubscriptionsResponse
DescribeNotificationSubscriptionsResponse'
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
"Marker")
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
"Subscriptions" 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
DescribeNotificationSubscriptions
where
hashWithSalt :: Int -> DescribeNotificationSubscriptions -> Int
hashWithSalt
Int
_salt
DescribeNotificationSubscriptions' {Maybe Natural
Maybe Text
Text
organizationId :: Text
marker :: Maybe Text
limit :: Maybe Natural
$sel:organizationId:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Text
$sel:marker:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Maybe Text
$sel:limit:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Maybe Natural
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
organizationId
instance
Prelude.NFData
DescribeNotificationSubscriptions
where
rnf :: DescribeNotificationSubscriptions -> ()
rnf DescribeNotificationSubscriptions' {Maybe Natural
Maybe Text
Text
organizationId :: Text
marker :: Maybe Text
limit :: Maybe Natural
$sel:organizationId:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Text
$sel:marker:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Maybe Text
$sel:limit:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Maybe Natural
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
organizationId
instance
Data.ToHeaders
DescribeNotificationSubscriptions
where
toHeaders :: DescribeNotificationSubscriptions -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance
Data.ToPath
DescribeNotificationSubscriptions
where
toPath :: DescribeNotificationSubscriptions -> ByteString
toPath DescribeNotificationSubscriptions' {Maybe Natural
Maybe Text
Text
organizationId :: Text
marker :: Maybe Text
limit :: Maybe Natural
$sel:organizationId:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Text
$sel:marker:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Maybe Text
$sel:limit:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Maybe Natural
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"/api/v1/organizations/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
organizationId,
ByteString
"/subscriptions"
]
instance
Data.ToQuery
DescribeNotificationSubscriptions
where
toQuery :: DescribeNotificationSubscriptions -> QueryString
toQuery DescribeNotificationSubscriptions' {Maybe Natural
Maybe Text
Text
organizationId :: Text
marker :: Maybe Text
limit :: Maybe Natural
$sel:organizationId:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Text
$sel:marker:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Maybe Text
$sel:limit:DescribeNotificationSubscriptions' :: DescribeNotificationSubscriptions -> Maybe Natural
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"limit" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
limit, ByteString
"marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker]
data DescribeNotificationSubscriptionsResponse = DescribeNotificationSubscriptionsResponse'
{
DescribeNotificationSubscriptionsResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
DescribeNotificationSubscriptionsResponse -> Maybe [Subscription]
subscriptions :: Prelude.Maybe [Subscription],
DescribeNotificationSubscriptionsResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DescribeNotificationSubscriptionsResponse
-> DescribeNotificationSubscriptionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeNotificationSubscriptionsResponse
-> DescribeNotificationSubscriptionsResponse -> Bool
$c/= :: DescribeNotificationSubscriptionsResponse
-> DescribeNotificationSubscriptionsResponse -> Bool
== :: DescribeNotificationSubscriptionsResponse
-> DescribeNotificationSubscriptionsResponse -> Bool
$c== :: DescribeNotificationSubscriptionsResponse
-> DescribeNotificationSubscriptionsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeNotificationSubscriptionsResponse]
ReadPrec DescribeNotificationSubscriptionsResponse
Int -> ReadS DescribeNotificationSubscriptionsResponse
ReadS [DescribeNotificationSubscriptionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeNotificationSubscriptionsResponse]
$creadListPrec :: ReadPrec [DescribeNotificationSubscriptionsResponse]
readPrec :: ReadPrec DescribeNotificationSubscriptionsResponse
$creadPrec :: ReadPrec DescribeNotificationSubscriptionsResponse
readList :: ReadS [DescribeNotificationSubscriptionsResponse]
$creadList :: ReadS [DescribeNotificationSubscriptionsResponse]
readsPrec :: Int -> ReadS DescribeNotificationSubscriptionsResponse
$creadsPrec :: Int -> ReadS DescribeNotificationSubscriptionsResponse
Prelude.Read, Int -> DescribeNotificationSubscriptionsResponse -> ShowS
[DescribeNotificationSubscriptionsResponse] -> ShowS
DescribeNotificationSubscriptionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeNotificationSubscriptionsResponse] -> ShowS
$cshowList :: [DescribeNotificationSubscriptionsResponse] -> ShowS
show :: DescribeNotificationSubscriptionsResponse -> String
$cshow :: DescribeNotificationSubscriptionsResponse -> String
showsPrec :: Int -> DescribeNotificationSubscriptionsResponse -> ShowS
$cshowsPrec :: Int -> DescribeNotificationSubscriptionsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeNotificationSubscriptionsResponse x
-> DescribeNotificationSubscriptionsResponse
forall x.
DescribeNotificationSubscriptionsResponse
-> Rep DescribeNotificationSubscriptionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeNotificationSubscriptionsResponse x
-> DescribeNotificationSubscriptionsResponse
$cfrom :: forall x.
DescribeNotificationSubscriptionsResponse
-> Rep DescribeNotificationSubscriptionsResponse x
Prelude.Generic)
newDescribeNotificationSubscriptionsResponse ::
Prelude.Int ->
DescribeNotificationSubscriptionsResponse
newDescribeNotificationSubscriptionsResponse :: Int -> DescribeNotificationSubscriptionsResponse
newDescribeNotificationSubscriptionsResponse
Int
pHttpStatus_ =
DescribeNotificationSubscriptionsResponse'
{ $sel:marker:DescribeNotificationSubscriptionsResponse' :: Maybe Text
marker =
forall a. Maybe a
Prelude.Nothing,
$sel:subscriptions:DescribeNotificationSubscriptionsResponse' :: Maybe [Subscription]
subscriptions = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:DescribeNotificationSubscriptionsResponse' :: Int
httpStatus = Int
pHttpStatus_
}
describeNotificationSubscriptionsResponse_marker :: Lens.Lens' DescribeNotificationSubscriptionsResponse (Prelude.Maybe Prelude.Text)
describeNotificationSubscriptionsResponse_marker :: Lens' DescribeNotificationSubscriptionsResponse (Maybe Text)
describeNotificationSubscriptionsResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotificationSubscriptionsResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeNotificationSubscriptionsResponse' :: DescribeNotificationSubscriptionsResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeNotificationSubscriptionsResponse
s@DescribeNotificationSubscriptionsResponse' {} Maybe Text
a -> DescribeNotificationSubscriptionsResponse
s {$sel:marker:DescribeNotificationSubscriptionsResponse' :: Maybe Text
marker = Maybe Text
a} :: DescribeNotificationSubscriptionsResponse)
describeNotificationSubscriptionsResponse_subscriptions :: Lens.Lens' DescribeNotificationSubscriptionsResponse (Prelude.Maybe [Subscription])
describeNotificationSubscriptionsResponse_subscriptions :: Lens'
DescribeNotificationSubscriptionsResponse (Maybe [Subscription])
describeNotificationSubscriptionsResponse_subscriptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotificationSubscriptionsResponse' {Maybe [Subscription]
subscriptions :: Maybe [Subscription]
$sel:subscriptions:DescribeNotificationSubscriptionsResponse' :: DescribeNotificationSubscriptionsResponse -> Maybe [Subscription]
subscriptions} -> Maybe [Subscription]
subscriptions) (\s :: DescribeNotificationSubscriptionsResponse
s@DescribeNotificationSubscriptionsResponse' {} Maybe [Subscription]
a -> DescribeNotificationSubscriptionsResponse
s {$sel:subscriptions:DescribeNotificationSubscriptionsResponse' :: Maybe [Subscription]
subscriptions = Maybe [Subscription]
a} :: DescribeNotificationSubscriptionsResponse) 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
describeNotificationSubscriptionsResponse_httpStatus :: Lens.Lens' DescribeNotificationSubscriptionsResponse Prelude.Int
describeNotificationSubscriptionsResponse_httpStatus :: Lens' DescribeNotificationSubscriptionsResponse Int
describeNotificationSubscriptionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeNotificationSubscriptionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeNotificationSubscriptionsResponse' :: DescribeNotificationSubscriptionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeNotificationSubscriptionsResponse
s@DescribeNotificationSubscriptionsResponse' {} Int
a -> DescribeNotificationSubscriptionsResponse
s {$sel:httpStatus:DescribeNotificationSubscriptionsResponse' :: Int
httpStatus = Int
a} :: DescribeNotificationSubscriptionsResponse)
instance
Prelude.NFData
DescribeNotificationSubscriptionsResponse
where
rnf :: DescribeNotificationSubscriptionsResponse -> ()
rnf DescribeNotificationSubscriptionsResponse' {Int
Maybe [Subscription]
Maybe Text
httpStatus :: Int
subscriptions :: Maybe [Subscription]
marker :: Maybe Text
$sel:httpStatus:DescribeNotificationSubscriptionsResponse' :: DescribeNotificationSubscriptionsResponse -> Int
$sel:subscriptions:DescribeNotificationSubscriptionsResponse' :: DescribeNotificationSubscriptionsResponse -> Maybe [Subscription]
$sel:marker:DescribeNotificationSubscriptionsResponse' :: DescribeNotificationSubscriptionsResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Subscription]
subscriptions
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus