{-# 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.LicenseManagerLinuxSubscriptions.ListLinuxSubscriptions
-- 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 Linux subscriptions that have been discovered. If you have
-- linked your organization, the returned results will include data
-- aggregated across your accounts in Organizations.
--
-- This operation returns paginated results.
module Amazonka.LicenseManagerLinuxSubscriptions.ListLinuxSubscriptions
  ( -- * Creating a Request
    ListLinuxSubscriptions (..),
    newListLinuxSubscriptions,

    -- * Request Lenses
    listLinuxSubscriptions_filters,
    listLinuxSubscriptions_maxResults,
    listLinuxSubscriptions_nextToken,

    -- * Destructuring the Response
    ListLinuxSubscriptionsResponse (..),
    newListLinuxSubscriptionsResponse,

    -- * Response Lenses
    listLinuxSubscriptionsResponse_nextToken,
    listLinuxSubscriptionsResponse_subscriptions,
    listLinuxSubscriptionsResponse_httpStatus,
  )
where

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

-- | NextToken length limit is half of ddb accepted limit. Increase this
-- limit if parameters in request increases.
--
-- /See:/ 'newListLinuxSubscriptions' smart constructor.
data ListLinuxSubscriptions = ListLinuxSubscriptions'
  { -- | 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. For
    -- example, you can filter by the name of @Subscription@ with an optional
    -- operator to see subscriptions that match, partially match, or don\'t
    -- match a certain subscription\'s name.
    --
    -- The valid names for this filter are:
    --
    -- -   @Subscription@
    --
    -- The valid Operators for this filter are:
    --
    -- -   @contains@
    --
    -- -   @equals@
    --
    -- -   @Notequal@
    ListLinuxSubscriptions -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | Maximum number of results to return in a single call.
    ListLinuxSubscriptions -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | Token for the next set of results.
    ListLinuxSubscriptions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListLinuxSubscriptions -> ListLinuxSubscriptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLinuxSubscriptions -> ListLinuxSubscriptions -> Bool
$c/= :: ListLinuxSubscriptions -> ListLinuxSubscriptions -> Bool
== :: ListLinuxSubscriptions -> ListLinuxSubscriptions -> Bool
$c== :: ListLinuxSubscriptions -> ListLinuxSubscriptions -> Bool
Prelude.Eq, ReadPrec [ListLinuxSubscriptions]
ReadPrec ListLinuxSubscriptions
Int -> ReadS ListLinuxSubscriptions
ReadS [ListLinuxSubscriptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLinuxSubscriptions]
$creadListPrec :: ReadPrec [ListLinuxSubscriptions]
readPrec :: ReadPrec ListLinuxSubscriptions
$creadPrec :: ReadPrec ListLinuxSubscriptions
readList :: ReadS [ListLinuxSubscriptions]
$creadList :: ReadS [ListLinuxSubscriptions]
readsPrec :: Int -> ReadS ListLinuxSubscriptions
$creadsPrec :: Int -> ReadS ListLinuxSubscriptions
Prelude.Read, Int -> ListLinuxSubscriptions -> ShowS
[ListLinuxSubscriptions] -> ShowS
ListLinuxSubscriptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLinuxSubscriptions] -> ShowS
$cshowList :: [ListLinuxSubscriptions] -> ShowS
show :: ListLinuxSubscriptions -> String
$cshow :: ListLinuxSubscriptions -> String
showsPrec :: Int -> ListLinuxSubscriptions -> ShowS
$cshowsPrec :: Int -> ListLinuxSubscriptions -> ShowS
Prelude.Show, forall x. Rep ListLinuxSubscriptions x -> ListLinuxSubscriptions
forall x. ListLinuxSubscriptions -> Rep ListLinuxSubscriptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListLinuxSubscriptions x -> ListLinuxSubscriptions
$cfrom :: forall x. ListLinuxSubscriptions -> Rep ListLinuxSubscriptions x
Prelude.Generic)

-- |
-- Create a value of 'ListLinuxSubscriptions' 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', 'listLinuxSubscriptions_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. For
-- example, you can filter by the name of @Subscription@ with an optional
-- operator to see subscriptions that match, partially match, or don\'t
-- match a certain subscription\'s name.
--
-- The valid names for this filter are:
--
-- -   @Subscription@
--
-- The valid Operators for this filter are:
--
-- -   @contains@
--
-- -   @equals@
--
-- -   @Notequal@
--
-- 'maxResults', 'listLinuxSubscriptions_maxResults' - Maximum number of results to return in a single call.
--
-- 'nextToken', 'listLinuxSubscriptions_nextToken' - Token for the next set of results.
newListLinuxSubscriptions ::
  ListLinuxSubscriptions
newListLinuxSubscriptions :: ListLinuxSubscriptions
newListLinuxSubscriptions =
  ListLinuxSubscriptions'
    { $sel:filters:ListLinuxSubscriptions' :: Maybe [Filter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListLinuxSubscriptions' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListLinuxSubscriptions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | 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. For
-- example, you can filter by the name of @Subscription@ with an optional
-- operator to see subscriptions that match, partially match, or don\'t
-- match a certain subscription\'s name.
--
-- The valid names for this filter are:
--
-- -   @Subscription@
--
-- The valid Operators for this filter are:
--
-- -   @contains@
--
-- -   @equals@
--
-- -   @Notequal@
listLinuxSubscriptions_filters :: Lens.Lens' ListLinuxSubscriptions (Prelude.Maybe [Filter])
listLinuxSubscriptions_filters :: Lens' ListLinuxSubscriptions (Maybe [Filter])
listLinuxSubscriptions_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLinuxSubscriptions' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:ListLinuxSubscriptions' :: ListLinuxSubscriptions -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: ListLinuxSubscriptions
s@ListLinuxSubscriptions' {} Maybe [Filter]
a -> ListLinuxSubscriptions
s {$sel:filters:ListLinuxSubscriptions' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: ListLinuxSubscriptions) 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.
listLinuxSubscriptions_maxResults :: Lens.Lens' ListLinuxSubscriptions (Prelude.Maybe Prelude.Int)
listLinuxSubscriptions_maxResults :: Lens' ListLinuxSubscriptions (Maybe Int)
listLinuxSubscriptions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLinuxSubscriptions' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:ListLinuxSubscriptions' :: ListLinuxSubscriptions -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: ListLinuxSubscriptions
s@ListLinuxSubscriptions' {} Maybe Int
a -> ListLinuxSubscriptions
s {$sel:maxResults:ListLinuxSubscriptions' :: Maybe Int
maxResults = Maybe Int
a} :: ListLinuxSubscriptions)

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

instance Core.AWSPager ListLinuxSubscriptions where
  page :: ListLinuxSubscriptions
-> AWSResponse ListLinuxSubscriptions
-> Maybe ListLinuxSubscriptions
page ListLinuxSubscriptions
rq AWSResponse ListLinuxSubscriptions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListLinuxSubscriptions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLinuxSubscriptionsResponse (Maybe Text)
listLinuxSubscriptionsResponse_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 ListLinuxSubscriptions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLinuxSubscriptionsResponse (Maybe [Subscription])
listLinuxSubscriptionsResponse_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.$ ListLinuxSubscriptions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListLinuxSubscriptions (Maybe Text)
listLinuxSubscriptions_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListLinuxSubscriptions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLinuxSubscriptionsResponse (Maybe Text)
listLinuxSubscriptionsResponse_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 ListLinuxSubscriptions where
  type
    AWSResponse ListLinuxSubscriptions =
      ListLinuxSubscriptionsResponse
  request :: (Service -> Service)
-> ListLinuxSubscriptions -> Request ListLinuxSubscriptions
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 ListLinuxSubscriptions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListLinuxSubscriptions)))
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 -> ListLinuxSubscriptionsResponse
ListLinuxSubscriptionsResponse'
            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
"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 ListLinuxSubscriptions where
  hashWithSalt :: Int -> ListLinuxSubscriptions -> Int
hashWithSalt Int
_salt ListLinuxSubscriptions' {Maybe Int
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:nextToken:ListLinuxSubscriptions' :: ListLinuxSubscriptions -> Maybe Text
$sel:maxResults:ListLinuxSubscriptions' :: ListLinuxSubscriptions -> Maybe Int
$sel:filters:ListLinuxSubscriptions' :: ListLinuxSubscriptions -> 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

instance Prelude.NFData ListLinuxSubscriptions where
  rnf :: ListLinuxSubscriptions -> ()
rnf ListLinuxSubscriptions' {Maybe Int
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:nextToken:ListLinuxSubscriptions' :: ListLinuxSubscriptions -> Maybe Text
$sel:maxResults:ListLinuxSubscriptions' :: ListLinuxSubscriptions -> Maybe Int
$sel:filters:ListLinuxSubscriptions' :: ListLinuxSubscriptions -> 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

instance Data.ToHeaders ListLinuxSubscriptions where
  toHeaders :: ListLinuxSubscriptions -> 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 ListLinuxSubscriptions where
  toJSON :: ListLinuxSubscriptions -> Value
toJSON ListLinuxSubscriptions' {Maybe Int
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:nextToken:ListLinuxSubscriptions' :: ListLinuxSubscriptions -> Maybe Text
$sel:maxResults:ListLinuxSubscriptions' :: ListLinuxSubscriptions -> Maybe Int
$sel:filters:ListLinuxSubscriptions' :: ListLinuxSubscriptions -> 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
          ]
      )

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

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

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

-- |
-- Create a value of 'ListLinuxSubscriptionsResponse' 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', 'listLinuxSubscriptionsResponse_nextToken' - Token for the next set of results.
--
-- 'subscriptions', 'listLinuxSubscriptionsResponse_subscriptions' - An array that contains subscription objects.
--
-- 'httpStatus', 'listLinuxSubscriptionsResponse_httpStatus' - The response's http status code.
newListLinuxSubscriptionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListLinuxSubscriptionsResponse
newListLinuxSubscriptionsResponse :: Int -> ListLinuxSubscriptionsResponse
newListLinuxSubscriptionsResponse Int
pHttpStatus_ =
  ListLinuxSubscriptionsResponse'
    { $sel:nextToken:ListLinuxSubscriptionsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:subscriptions:ListLinuxSubscriptionsResponse' :: Maybe [Subscription]
subscriptions = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListLinuxSubscriptionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | An array that contains subscription objects.
listLinuxSubscriptionsResponse_subscriptions :: Lens.Lens' ListLinuxSubscriptionsResponse (Prelude.Maybe [Subscription])
listLinuxSubscriptionsResponse_subscriptions :: Lens' ListLinuxSubscriptionsResponse (Maybe [Subscription])
listLinuxSubscriptionsResponse_subscriptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLinuxSubscriptionsResponse' {Maybe [Subscription]
subscriptions :: Maybe [Subscription]
$sel:subscriptions:ListLinuxSubscriptionsResponse' :: ListLinuxSubscriptionsResponse -> Maybe [Subscription]
subscriptions} -> Maybe [Subscription]
subscriptions) (\s :: ListLinuxSubscriptionsResponse
s@ListLinuxSubscriptionsResponse' {} Maybe [Subscription]
a -> ListLinuxSubscriptionsResponse
s {$sel:subscriptions:ListLinuxSubscriptionsResponse' :: Maybe [Subscription]
subscriptions = Maybe [Subscription]
a} :: ListLinuxSubscriptionsResponse) 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.
listLinuxSubscriptionsResponse_httpStatus :: Lens.Lens' ListLinuxSubscriptionsResponse Prelude.Int
listLinuxSubscriptionsResponse_httpStatus :: Lens' ListLinuxSubscriptionsResponse Int
listLinuxSubscriptionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLinuxSubscriptionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListLinuxSubscriptionsResponse' :: ListLinuxSubscriptionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListLinuxSubscriptionsResponse
s@ListLinuxSubscriptionsResponse' {} Int
a -> ListLinuxSubscriptionsResponse
s {$sel:httpStatus:ListLinuxSubscriptionsResponse' :: Int
httpStatus = Int
a} :: ListLinuxSubscriptionsResponse)

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