{-# 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.LicenseManagerUserSubscriptions.ListProductSubscriptions
-- 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 user-based subscription products available from an identity
-- provider.
--
-- This operation returns paginated results.
module Amazonka.LicenseManagerUserSubscriptions.ListProductSubscriptions
  ( -- * Creating a Request
    ListProductSubscriptions (..),
    newListProductSubscriptions,

    -- * Request Lenses
    listProductSubscriptions_filters,
    listProductSubscriptions_maxResults,
    listProductSubscriptions_nextToken,
    listProductSubscriptions_identityProvider,
    listProductSubscriptions_product,

    -- * Destructuring the Response
    ListProductSubscriptionsResponse (..),
    newListProductSubscriptionsResponse,

    -- * Response Lenses
    listProductSubscriptionsResponse_nextToken,
    listProductSubscriptionsResponse_productUserSummaries,
    listProductSubscriptionsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.LicenseManagerUserSubscriptions.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListProductSubscriptions' smart constructor.
data ListProductSubscriptions = ListProductSubscriptions'
  { -- | An array of structures that you can use to filter the results to those
    -- that match one or more sets of key-value pairs that you specify.
    ListProductSubscriptions -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | Maximum number of results to return in a single call.
    ListProductSubscriptions -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | Token for the next set of results.
    ListProductSubscriptions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An object that specifies details for the identity provider.
    ListProductSubscriptions -> IdentityProvider
identityProvider :: IdentityProvider,
    -- | The name of the user-based subscription product.
    ListProductSubscriptions -> Text
product :: Prelude.Text
  }
  deriving (ListProductSubscriptions -> ListProductSubscriptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListProductSubscriptions -> ListProductSubscriptions -> Bool
$c/= :: ListProductSubscriptions -> ListProductSubscriptions -> Bool
== :: ListProductSubscriptions -> ListProductSubscriptions -> Bool
$c== :: ListProductSubscriptions -> ListProductSubscriptions -> Bool
Prelude.Eq, ReadPrec [ListProductSubscriptions]
ReadPrec ListProductSubscriptions
Int -> ReadS ListProductSubscriptions
ReadS [ListProductSubscriptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListProductSubscriptions]
$creadListPrec :: ReadPrec [ListProductSubscriptions]
readPrec :: ReadPrec ListProductSubscriptions
$creadPrec :: ReadPrec ListProductSubscriptions
readList :: ReadS [ListProductSubscriptions]
$creadList :: ReadS [ListProductSubscriptions]
readsPrec :: Int -> ReadS ListProductSubscriptions
$creadsPrec :: Int -> ReadS ListProductSubscriptions
Prelude.Read, Int -> ListProductSubscriptions -> ShowS
[ListProductSubscriptions] -> ShowS
ListProductSubscriptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListProductSubscriptions] -> ShowS
$cshowList :: [ListProductSubscriptions] -> ShowS
show :: ListProductSubscriptions -> String
$cshow :: ListProductSubscriptions -> String
showsPrec :: Int -> ListProductSubscriptions -> ShowS
$cshowsPrec :: Int -> ListProductSubscriptions -> ShowS
Prelude.Show, forall x.
Rep ListProductSubscriptions x -> ListProductSubscriptions
forall x.
ListProductSubscriptions -> Rep ListProductSubscriptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListProductSubscriptions x -> ListProductSubscriptions
$cfrom :: forall x.
ListProductSubscriptions -> Rep ListProductSubscriptions x
Prelude.Generic)

-- |
-- Create a value of 'ListProductSubscriptions' 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:
--
-- 'filters', 'listProductSubscriptions_filters' - An array of structures that you can use to filter the results to those
-- that match one or more sets of key-value pairs that you specify.
--
-- 'maxResults', 'listProductSubscriptions_maxResults' - Maximum number of results to return in a single call.
--
-- 'nextToken', 'listProductSubscriptions_nextToken' - Token for the next set of results.
--
-- 'identityProvider', 'listProductSubscriptions_identityProvider' - An object that specifies details for the identity provider.
--
-- 'product', 'listProductSubscriptions_product' - The name of the user-based subscription product.
newListProductSubscriptions ::
  -- | 'identityProvider'
  IdentityProvider ->
  -- | 'product'
  Prelude.Text ->
  ListProductSubscriptions
newListProductSubscriptions :: IdentityProvider -> Text -> ListProductSubscriptions
newListProductSubscriptions
  IdentityProvider
pIdentityProvider_
  Text
pProduct_ =
    ListProductSubscriptions'
      { $sel:filters:ListProductSubscriptions' :: Maybe [Filter]
filters =
          forall a. Maybe a
Prelude.Nothing,
        $sel:maxResults:ListProductSubscriptions' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListProductSubscriptions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:identityProvider:ListProductSubscriptions' :: IdentityProvider
identityProvider = IdentityProvider
pIdentityProvider_,
        $sel:product:ListProductSubscriptions' :: Text
product = Text
pProduct_
      }

-- | An array of structures that you can use to filter the results to those
-- that match one or more sets of key-value pairs that you specify.
listProductSubscriptions_filters :: Lens.Lens' ListProductSubscriptions (Prelude.Maybe [Filter])
listProductSubscriptions_filters :: Lens' ListProductSubscriptions (Maybe [Filter])
listProductSubscriptions_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListProductSubscriptions' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: ListProductSubscriptions
s@ListProductSubscriptions' {} Maybe [Filter]
a -> ListProductSubscriptions
s {$sel:filters:ListProductSubscriptions' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: ListProductSubscriptions) 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

-- | Maximum number of results to return in a single call.
listProductSubscriptions_maxResults :: Lens.Lens' ListProductSubscriptions (Prelude.Maybe Prelude.Int)
listProductSubscriptions_maxResults :: Lens' ListProductSubscriptions (Maybe Int)
listProductSubscriptions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListProductSubscriptions' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: ListProductSubscriptions
s@ListProductSubscriptions' {} Maybe Int
a -> ListProductSubscriptions
s {$sel:maxResults:ListProductSubscriptions' :: Maybe Int
maxResults = Maybe Int
a} :: ListProductSubscriptions)

-- | Token for the next set of results.
listProductSubscriptions_nextToken :: Lens.Lens' ListProductSubscriptions (Prelude.Maybe Prelude.Text)
listProductSubscriptions_nextToken :: Lens' ListProductSubscriptions (Maybe Text)
listProductSubscriptions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListProductSubscriptions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListProductSubscriptions
s@ListProductSubscriptions' {} Maybe Text
a -> ListProductSubscriptions
s {$sel:nextToken:ListProductSubscriptions' :: Maybe Text
nextToken = Maybe Text
a} :: ListProductSubscriptions)

-- | An object that specifies details for the identity provider.
listProductSubscriptions_identityProvider :: Lens.Lens' ListProductSubscriptions IdentityProvider
listProductSubscriptions_identityProvider :: Lens' ListProductSubscriptions IdentityProvider
listProductSubscriptions_identityProvider = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListProductSubscriptions' {IdentityProvider
identityProvider :: IdentityProvider
$sel:identityProvider:ListProductSubscriptions' :: ListProductSubscriptions -> IdentityProvider
identityProvider} -> IdentityProvider
identityProvider) (\s :: ListProductSubscriptions
s@ListProductSubscriptions' {} IdentityProvider
a -> ListProductSubscriptions
s {$sel:identityProvider:ListProductSubscriptions' :: IdentityProvider
identityProvider = IdentityProvider
a} :: ListProductSubscriptions)

-- | The name of the user-based subscription product.
listProductSubscriptions_product :: Lens.Lens' ListProductSubscriptions Prelude.Text
listProductSubscriptions_product :: Lens' ListProductSubscriptions Text
listProductSubscriptions_product = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListProductSubscriptions' {Text
product :: Text
$sel:product:ListProductSubscriptions' :: ListProductSubscriptions -> Text
product} -> Text
product) (\s :: ListProductSubscriptions
s@ListProductSubscriptions' {} Text
a -> ListProductSubscriptions
s {$sel:product:ListProductSubscriptions' :: Text
product = Text
a} :: ListProductSubscriptions)

instance Core.AWSPager ListProductSubscriptions where
  page :: ListProductSubscriptions
-> AWSResponse ListProductSubscriptions
-> Maybe ListProductSubscriptions
page ListProductSubscriptions
rq AWSResponse ListProductSubscriptions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListProductSubscriptions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListProductSubscriptionsResponse (Maybe Text)
listProductSubscriptionsResponse_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 ListProductSubscriptions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListProductSubscriptionsResponse (Maybe [ProductUserSummary])
listProductSubscriptionsResponse_productUserSummaries
            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.$ ListProductSubscriptions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListProductSubscriptions (Maybe Text)
listProductSubscriptions_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListProductSubscriptions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListProductSubscriptionsResponse (Maybe Text)
listProductSubscriptionsResponse_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 ListProductSubscriptions where
  type
    AWSResponse ListProductSubscriptions =
      ListProductSubscriptionsResponse
  request :: (Service -> Service)
-> ListProductSubscriptions -> Request ListProductSubscriptions
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 ListProductSubscriptions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListProductSubscriptions)))
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 [ProductUserSummary]
-> Int
-> ListProductSubscriptionsResponse
ListProductSubscriptionsResponse'
            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
"ProductUserSummaries"
                            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 ListProductSubscriptions where
  hashWithSalt :: Int -> ListProductSubscriptions -> Int
hashWithSalt Int
_salt ListProductSubscriptions' {Maybe Int
Maybe [Filter]
Maybe Text
Text
IdentityProvider
product :: Text
identityProvider :: IdentityProvider
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:product:ListProductSubscriptions' :: ListProductSubscriptions -> Text
$sel:identityProvider:ListProductSubscriptions' :: ListProductSubscriptions -> IdentityProvider
$sel:nextToken:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe Text
$sel:maxResults:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe Int
$sel:filters:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe [Filter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Filter]
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` IdentityProvider
identityProvider
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
product

instance Prelude.NFData ListProductSubscriptions where
  rnf :: ListProductSubscriptions -> ()
rnf ListProductSubscriptions' {Maybe Int
Maybe [Filter]
Maybe Text
Text
IdentityProvider
product :: Text
identityProvider :: IdentityProvider
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:product:ListProductSubscriptions' :: ListProductSubscriptions -> Text
$sel:identityProvider:ListProductSubscriptions' :: ListProductSubscriptions -> IdentityProvider
$sel:nextToken:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe Text
$sel:maxResults:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe Int
$sel:filters:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe [Filter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Filter]
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
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 IdentityProvider
identityProvider
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
product

instance Data.ToHeaders ListProductSubscriptions where
  toHeaders :: ListProductSubscriptions -> 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.ToJSON ListProductSubscriptions where
  toJSON :: ListProductSubscriptions -> Value
toJSON ListProductSubscriptions' {Maybe Int
Maybe [Filter]
Maybe Text
Text
IdentityProvider
product :: Text
identityProvider :: IdentityProvider
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:product:ListProductSubscriptions' :: ListProductSubscriptions -> Text
$sel:identityProvider:ListProductSubscriptions' :: ListProductSubscriptions -> IdentityProvider
$sel:nextToken:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe Text
$sel:maxResults:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe Int
$sel:filters:ListProductSubscriptions' :: ListProductSubscriptions -> Maybe [Filter]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filters" 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 [Filter]
filters,
            (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 Int
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
"IdentityProvider" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= IdentityProvider
identityProvider),
            forall a. a -> Maybe a
Prelude.Just (Key
"Product" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
product)
          ]
      )

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

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

-- | /See:/ 'newListProductSubscriptionsResponse' smart constructor.
data ListProductSubscriptionsResponse = ListProductSubscriptionsResponse'
  { -- | Token for the next set of results.
    ListProductSubscriptionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Metadata that describes the list product subscriptions operation.
    ListProductSubscriptionsResponse -> Maybe [ProductUserSummary]
productUserSummaries :: Prelude.Maybe [ProductUserSummary],
    -- | The response's http status code.
    ListProductSubscriptionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListProductSubscriptionsResponse
-> ListProductSubscriptionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListProductSubscriptionsResponse
-> ListProductSubscriptionsResponse -> Bool
$c/= :: ListProductSubscriptionsResponse
-> ListProductSubscriptionsResponse -> Bool
== :: ListProductSubscriptionsResponse
-> ListProductSubscriptionsResponse -> Bool
$c== :: ListProductSubscriptionsResponse
-> ListProductSubscriptionsResponse -> Bool
Prelude.Eq, ReadPrec [ListProductSubscriptionsResponse]
ReadPrec ListProductSubscriptionsResponse
Int -> ReadS ListProductSubscriptionsResponse
ReadS [ListProductSubscriptionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListProductSubscriptionsResponse]
$creadListPrec :: ReadPrec [ListProductSubscriptionsResponse]
readPrec :: ReadPrec ListProductSubscriptionsResponse
$creadPrec :: ReadPrec ListProductSubscriptionsResponse
readList :: ReadS [ListProductSubscriptionsResponse]
$creadList :: ReadS [ListProductSubscriptionsResponse]
readsPrec :: Int -> ReadS ListProductSubscriptionsResponse
$creadsPrec :: Int -> ReadS ListProductSubscriptionsResponse
Prelude.Read, Int -> ListProductSubscriptionsResponse -> ShowS
[ListProductSubscriptionsResponse] -> ShowS
ListProductSubscriptionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListProductSubscriptionsResponse] -> ShowS
$cshowList :: [ListProductSubscriptionsResponse] -> ShowS
show :: ListProductSubscriptionsResponse -> String
$cshow :: ListProductSubscriptionsResponse -> String
showsPrec :: Int -> ListProductSubscriptionsResponse -> ShowS
$cshowsPrec :: Int -> ListProductSubscriptionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListProductSubscriptionsResponse x
-> ListProductSubscriptionsResponse
forall x.
ListProductSubscriptionsResponse
-> Rep ListProductSubscriptionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListProductSubscriptionsResponse x
-> ListProductSubscriptionsResponse
$cfrom :: forall x.
ListProductSubscriptionsResponse
-> Rep ListProductSubscriptionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListProductSubscriptionsResponse' 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', 'listProductSubscriptionsResponse_nextToken' - Token for the next set of results.
--
-- 'productUserSummaries', 'listProductSubscriptionsResponse_productUserSummaries' - Metadata that describes the list product subscriptions operation.
--
-- 'httpStatus', 'listProductSubscriptionsResponse_httpStatus' - The response's http status code.
newListProductSubscriptionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListProductSubscriptionsResponse
newListProductSubscriptionsResponse :: Int -> ListProductSubscriptionsResponse
newListProductSubscriptionsResponse Int
pHttpStatus_ =
  ListProductSubscriptionsResponse'
    { $sel:nextToken:ListProductSubscriptionsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:productUserSummaries:ListProductSubscriptionsResponse' :: Maybe [ProductUserSummary]
productUserSummaries = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListProductSubscriptionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Token for the next set of results.
listProductSubscriptionsResponse_nextToken :: Lens.Lens' ListProductSubscriptionsResponse (Prelude.Maybe Prelude.Text)
listProductSubscriptionsResponse_nextToken :: Lens' ListProductSubscriptionsResponse (Maybe Text)
listProductSubscriptionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListProductSubscriptionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListProductSubscriptionsResponse' :: ListProductSubscriptionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListProductSubscriptionsResponse
s@ListProductSubscriptionsResponse' {} Maybe Text
a -> ListProductSubscriptionsResponse
s {$sel:nextToken:ListProductSubscriptionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListProductSubscriptionsResponse)

-- | Metadata that describes the list product subscriptions operation.
listProductSubscriptionsResponse_productUserSummaries :: Lens.Lens' ListProductSubscriptionsResponse (Prelude.Maybe [ProductUserSummary])
listProductSubscriptionsResponse_productUserSummaries :: Lens' ListProductSubscriptionsResponse (Maybe [ProductUserSummary])
listProductSubscriptionsResponse_productUserSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListProductSubscriptionsResponse' {Maybe [ProductUserSummary]
productUserSummaries :: Maybe [ProductUserSummary]
$sel:productUserSummaries:ListProductSubscriptionsResponse' :: ListProductSubscriptionsResponse -> Maybe [ProductUserSummary]
productUserSummaries} -> Maybe [ProductUserSummary]
productUserSummaries) (\s :: ListProductSubscriptionsResponse
s@ListProductSubscriptionsResponse' {} Maybe [ProductUserSummary]
a -> ListProductSubscriptionsResponse
s {$sel:productUserSummaries:ListProductSubscriptionsResponse' :: Maybe [ProductUserSummary]
productUserSummaries = Maybe [ProductUserSummary]
a} :: ListProductSubscriptionsResponse) 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.
listProductSubscriptionsResponse_httpStatus :: Lens.Lens' ListProductSubscriptionsResponse Prelude.Int
listProductSubscriptionsResponse_httpStatus :: Lens' ListProductSubscriptionsResponse Int
listProductSubscriptionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListProductSubscriptionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListProductSubscriptionsResponse' :: ListProductSubscriptionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListProductSubscriptionsResponse
s@ListProductSubscriptionsResponse' {} Int
a -> ListProductSubscriptionsResponse
s {$sel:httpStatus:ListProductSubscriptionsResponse' :: Int
httpStatus = Int
a} :: ListProductSubscriptionsResponse)

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