{-# 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.MarketplaceCatalog.ListChangeSets
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the list of change sets owned by the account being used to make
-- the call. You can filter this list by providing any combination of
-- @entityId@, @ChangeSetName@, and status. If you provide more than one
-- filter, the API operation applies a logical AND between the filters.
--
-- You can describe a change during the 60-day request history retention
-- period for API calls.
module Amazonka.MarketplaceCatalog.ListChangeSets
  ( -- * Creating a Request
    ListChangeSets (..),
    newListChangeSets,

    -- * Request Lenses
    listChangeSets_filterList,
    listChangeSets_maxResults,
    listChangeSets_nextToken,
    listChangeSets_sort,
    listChangeSets_catalog,

    -- * Destructuring the Response
    ListChangeSetsResponse (..),
    newListChangeSetsResponse,

    -- * Response Lenses
    listChangeSetsResponse_changeSetSummaryList,
    listChangeSetsResponse_nextToken,
    listChangeSetsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListChangeSets' smart constructor.
data ListChangeSets = ListChangeSets'
  { -- | An array of filter objects.
    ListChangeSets -> Maybe (NonEmpty Filter)
filterList :: Prelude.Maybe (Prelude.NonEmpty Filter),
    -- | The maximum number of results returned by a single call. This value must
    -- be provided in the next call to retrieve the next set of results. By
    -- default, this value is 20.
    ListChangeSets -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token value retrieved from a previous call to access the next page
    -- of results.
    ListChangeSets -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An object that contains two attributes, @SortBy@ and @SortOrder@.
    ListChangeSets -> Maybe Sort
sort :: Prelude.Maybe Sort,
    -- | The catalog related to the request. Fixed value: @AWSMarketplace@
    ListChangeSets -> Text
catalog :: Prelude.Text
  }
  deriving (ListChangeSets -> ListChangeSets -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListChangeSets -> ListChangeSets -> Bool
$c/= :: ListChangeSets -> ListChangeSets -> Bool
== :: ListChangeSets -> ListChangeSets -> Bool
$c== :: ListChangeSets -> ListChangeSets -> Bool
Prelude.Eq, ReadPrec [ListChangeSets]
ReadPrec ListChangeSets
Int -> ReadS ListChangeSets
ReadS [ListChangeSets]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListChangeSets]
$creadListPrec :: ReadPrec [ListChangeSets]
readPrec :: ReadPrec ListChangeSets
$creadPrec :: ReadPrec ListChangeSets
readList :: ReadS [ListChangeSets]
$creadList :: ReadS [ListChangeSets]
readsPrec :: Int -> ReadS ListChangeSets
$creadsPrec :: Int -> ReadS ListChangeSets
Prelude.Read, Int -> ListChangeSets -> ShowS
[ListChangeSets] -> ShowS
ListChangeSets -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListChangeSets] -> ShowS
$cshowList :: [ListChangeSets] -> ShowS
show :: ListChangeSets -> String
$cshow :: ListChangeSets -> String
showsPrec :: Int -> ListChangeSets -> ShowS
$cshowsPrec :: Int -> ListChangeSets -> ShowS
Prelude.Show, forall x. Rep ListChangeSets x -> ListChangeSets
forall x. ListChangeSets -> Rep ListChangeSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListChangeSets x -> ListChangeSets
$cfrom :: forall x. ListChangeSets -> Rep ListChangeSets x
Prelude.Generic)

-- |
-- Create a value of 'ListChangeSets' 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:
--
-- 'filterList', 'listChangeSets_filterList' - An array of filter objects.
--
-- 'maxResults', 'listChangeSets_maxResults' - The maximum number of results returned by a single call. This value must
-- be provided in the next call to retrieve the next set of results. By
-- default, this value is 20.
--
-- 'nextToken', 'listChangeSets_nextToken' - The token value retrieved from a previous call to access the next page
-- of results.
--
-- 'sort', 'listChangeSets_sort' - An object that contains two attributes, @SortBy@ and @SortOrder@.
--
-- 'catalog', 'listChangeSets_catalog' - The catalog related to the request. Fixed value: @AWSMarketplace@
newListChangeSets ::
  -- | 'catalog'
  Prelude.Text ->
  ListChangeSets
newListChangeSets :: Text -> ListChangeSets
newListChangeSets Text
pCatalog_ =
  ListChangeSets'
    { $sel:filterList:ListChangeSets' :: Maybe (NonEmpty Filter)
filterList = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListChangeSets' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListChangeSets' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sort:ListChangeSets' :: Maybe Sort
sort = forall a. Maybe a
Prelude.Nothing,
      $sel:catalog:ListChangeSets' :: Text
catalog = Text
pCatalog_
    }

-- | An array of filter objects.
listChangeSets_filterList :: Lens.Lens' ListChangeSets (Prelude.Maybe (Prelude.NonEmpty Filter))
listChangeSets_filterList :: Lens' ListChangeSets (Maybe (NonEmpty Filter))
listChangeSets_filterList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangeSets' {Maybe (NonEmpty Filter)
filterList :: Maybe (NonEmpty Filter)
$sel:filterList:ListChangeSets' :: ListChangeSets -> Maybe (NonEmpty Filter)
filterList} -> Maybe (NonEmpty Filter)
filterList) (\s :: ListChangeSets
s@ListChangeSets' {} Maybe (NonEmpty Filter)
a -> ListChangeSets
s {$sel:filterList:ListChangeSets' :: Maybe (NonEmpty Filter)
filterList = Maybe (NonEmpty Filter)
a} :: ListChangeSets) 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 results returned by a single call. This value must
-- be provided in the next call to retrieve the next set of results. By
-- default, this value is 20.
listChangeSets_maxResults :: Lens.Lens' ListChangeSets (Prelude.Maybe Prelude.Natural)
listChangeSets_maxResults :: Lens' ListChangeSets (Maybe Natural)
listChangeSets_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangeSets' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListChangeSets' :: ListChangeSets -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListChangeSets
s@ListChangeSets' {} Maybe Natural
a -> ListChangeSets
s {$sel:maxResults:ListChangeSets' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListChangeSets)

-- | The token value retrieved from a previous call to access the next page
-- of results.
listChangeSets_nextToken :: Lens.Lens' ListChangeSets (Prelude.Maybe Prelude.Text)
listChangeSets_nextToken :: Lens' ListChangeSets (Maybe Text)
listChangeSets_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangeSets' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListChangeSets' :: ListChangeSets -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListChangeSets
s@ListChangeSets' {} Maybe Text
a -> ListChangeSets
s {$sel:nextToken:ListChangeSets' :: Maybe Text
nextToken = Maybe Text
a} :: ListChangeSets)

-- | An object that contains two attributes, @SortBy@ and @SortOrder@.
listChangeSets_sort :: Lens.Lens' ListChangeSets (Prelude.Maybe Sort)
listChangeSets_sort :: Lens' ListChangeSets (Maybe Sort)
listChangeSets_sort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangeSets' {Maybe Sort
sort :: Maybe Sort
$sel:sort:ListChangeSets' :: ListChangeSets -> Maybe Sort
sort} -> Maybe Sort
sort) (\s :: ListChangeSets
s@ListChangeSets' {} Maybe Sort
a -> ListChangeSets
s {$sel:sort:ListChangeSets' :: Maybe Sort
sort = Maybe Sort
a} :: ListChangeSets)

-- | The catalog related to the request. Fixed value: @AWSMarketplace@
listChangeSets_catalog :: Lens.Lens' ListChangeSets Prelude.Text
listChangeSets_catalog :: Lens' ListChangeSets Text
listChangeSets_catalog = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangeSets' {Text
catalog :: Text
$sel:catalog:ListChangeSets' :: ListChangeSets -> Text
catalog} -> Text
catalog) (\s :: ListChangeSets
s@ListChangeSets' {} Text
a -> ListChangeSets
s {$sel:catalog:ListChangeSets' :: Text
catalog = Text
a} :: ListChangeSets)

instance Core.AWSRequest ListChangeSets where
  type
    AWSResponse ListChangeSets =
      ListChangeSetsResponse
  request :: (Service -> Service) -> ListChangeSets -> Request ListChangeSets
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 ListChangeSets
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListChangeSets)))
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 [ChangeSetSummaryListItem]
-> Maybe Text -> Int -> ListChangeSetsResponse
ListChangeSetsResponse'
            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
"ChangeSetSummaryList"
                            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.<*> (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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListChangeSets where
  hashWithSalt :: Int -> ListChangeSets -> Int
hashWithSalt Int
_salt ListChangeSets' {Maybe Natural
Maybe (NonEmpty Filter)
Maybe Text
Maybe Sort
Text
catalog :: Text
sort :: Maybe Sort
nextToken :: Maybe Text
maxResults :: Maybe Natural
filterList :: Maybe (NonEmpty Filter)
$sel:catalog:ListChangeSets' :: ListChangeSets -> Text
$sel:sort:ListChangeSets' :: ListChangeSets -> Maybe Sort
$sel:nextToken:ListChangeSets' :: ListChangeSets -> Maybe Text
$sel:maxResults:ListChangeSets' :: ListChangeSets -> Maybe Natural
$sel:filterList:ListChangeSets' :: ListChangeSets -> Maybe (NonEmpty Filter)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Filter)
filterList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Sort
sort
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
catalog

instance Prelude.NFData ListChangeSets where
  rnf :: ListChangeSets -> ()
rnf ListChangeSets' {Maybe Natural
Maybe (NonEmpty Filter)
Maybe Text
Maybe Sort
Text
catalog :: Text
sort :: Maybe Sort
nextToken :: Maybe Text
maxResults :: Maybe Natural
filterList :: Maybe (NonEmpty Filter)
$sel:catalog:ListChangeSets' :: ListChangeSets -> Text
$sel:sort:ListChangeSets' :: ListChangeSets -> Maybe Sort
$sel:nextToken:ListChangeSets' :: ListChangeSets -> Maybe Text
$sel:maxResults:ListChangeSets' :: ListChangeSets -> Maybe Natural
$sel:filterList:ListChangeSets' :: ListChangeSets -> Maybe (NonEmpty Filter)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Filter)
filterList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Sort
sort
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
catalog

instance Data.ToHeaders ListChangeSets where
  toHeaders :: ListChangeSets -> 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 ListChangeSets where
  toJSON :: ListChangeSets -> Value
toJSON ListChangeSets' {Maybe Natural
Maybe (NonEmpty Filter)
Maybe Text
Maybe Sort
Text
catalog :: Text
sort :: Maybe Sort
nextToken :: Maybe Text
maxResults :: Maybe Natural
filterList :: Maybe (NonEmpty Filter)
$sel:catalog:ListChangeSets' :: ListChangeSets -> Text
$sel:sort:ListChangeSets' :: ListChangeSets -> Maybe Sort
$sel:nextToken:ListChangeSets' :: ListChangeSets -> Maybe Text
$sel:maxResults:ListChangeSets' :: ListChangeSets -> Maybe Natural
$sel:filterList:ListChangeSets' :: ListChangeSets -> Maybe (NonEmpty Filter)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"FilterList" 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 (NonEmpty Filter)
filterList,
            (Key
"MaxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            (Key
"Sort" 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 Sort
sort,
            forall a. a -> Maybe a
Prelude.Just (Key
"Catalog" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
catalog)
          ]
      )

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

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

-- | /See:/ 'newListChangeSetsResponse' smart constructor.
data ListChangeSetsResponse = ListChangeSetsResponse'
  { -- | Array of @ChangeSetSummaryListItem@ objects.
    ListChangeSetsResponse -> Maybe [ChangeSetSummaryListItem]
changeSetSummaryList :: Prelude.Maybe [ChangeSetSummaryListItem],
    -- | The value of the next token, if it exists. Null if there are no more
    -- results.
    ListChangeSetsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListChangeSetsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListChangeSetsResponse -> ListChangeSetsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListChangeSetsResponse -> ListChangeSetsResponse -> Bool
$c/= :: ListChangeSetsResponse -> ListChangeSetsResponse -> Bool
== :: ListChangeSetsResponse -> ListChangeSetsResponse -> Bool
$c== :: ListChangeSetsResponse -> ListChangeSetsResponse -> Bool
Prelude.Eq, ReadPrec [ListChangeSetsResponse]
ReadPrec ListChangeSetsResponse
Int -> ReadS ListChangeSetsResponse
ReadS [ListChangeSetsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListChangeSetsResponse]
$creadListPrec :: ReadPrec [ListChangeSetsResponse]
readPrec :: ReadPrec ListChangeSetsResponse
$creadPrec :: ReadPrec ListChangeSetsResponse
readList :: ReadS [ListChangeSetsResponse]
$creadList :: ReadS [ListChangeSetsResponse]
readsPrec :: Int -> ReadS ListChangeSetsResponse
$creadsPrec :: Int -> ReadS ListChangeSetsResponse
Prelude.Read, Int -> ListChangeSetsResponse -> ShowS
[ListChangeSetsResponse] -> ShowS
ListChangeSetsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListChangeSetsResponse] -> ShowS
$cshowList :: [ListChangeSetsResponse] -> ShowS
show :: ListChangeSetsResponse -> String
$cshow :: ListChangeSetsResponse -> String
showsPrec :: Int -> ListChangeSetsResponse -> ShowS
$cshowsPrec :: Int -> ListChangeSetsResponse -> ShowS
Prelude.Show, forall x. Rep ListChangeSetsResponse x -> ListChangeSetsResponse
forall x. ListChangeSetsResponse -> Rep ListChangeSetsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListChangeSetsResponse x -> ListChangeSetsResponse
$cfrom :: forall x. ListChangeSetsResponse -> Rep ListChangeSetsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListChangeSetsResponse' 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:
--
-- 'changeSetSummaryList', 'listChangeSetsResponse_changeSetSummaryList' - Array of @ChangeSetSummaryListItem@ objects.
--
-- 'nextToken', 'listChangeSetsResponse_nextToken' - The value of the next token, if it exists. Null if there are no more
-- results.
--
-- 'httpStatus', 'listChangeSetsResponse_httpStatus' - The response's http status code.
newListChangeSetsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListChangeSetsResponse
newListChangeSetsResponse :: Int -> ListChangeSetsResponse
newListChangeSetsResponse Int
pHttpStatus_ =
  ListChangeSetsResponse'
    { $sel:changeSetSummaryList:ListChangeSetsResponse' :: Maybe [ChangeSetSummaryListItem]
changeSetSummaryList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListChangeSetsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListChangeSetsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Array of @ChangeSetSummaryListItem@ objects.
listChangeSetsResponse_changeSetSummaryList :: Lens.Lens' ListChangeSetsResponse (Prelude.Maybe [ChangeSetSummaryListItem])
listChangeSetsResponse_changeSetSummaryList :: Lens' ListChangeSetsResponse (Maybe [ChangeSetSummaryListItem])
listChangeSetsResponse_changeSetSummaryList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangeSetsResponse' {Maybe [ChangeSetSummaryListItem]
changeSetSummaryList :: Maybe [ChangeSetSummaryListItem]
$sel:changeSetSummaryList:ListChangeSetsResponse' :: ListChangeSetsResponse -> Maybe [ChangeSetSummaryListItem]
changeSetSummaryList} -> Maybe [ChangeSetSummaryListItem]
changeSetSummaryList) (\s :: ListChangeSetsResponse
s@ListChangeSetsResponse' {} Maybe [ChangeSetSummaryListItem]
a -> ListChangeSetsResponse
s {$sel:changeSetSummaryList:ListChangeSetsResponse' :: Maybe [ChangeSetSummaryListItem]
changeSetSummaryList = Maybe [ChangeSetSummaryListItem]
a} :: ListChangeSetsResponse) 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 value of the next token, if it exists. Null if there are no more
-- results.
listChangeSetsResponse_nextToken :: Lens.Lens' ListChangeSetsResponse (Prelude.Maybe Prelude.Text)
listChangeSetsResponse_nextToken :: Lens' ListChangeSetsResponse (Maybe Text)
listChangeSetsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChangeSetsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListChangeSetsResponse' :: ListChangeSetsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListChangeSetsResponse
s@ListChangeSetsResponse' {} Maybe Text
a -> ListChangeSetsResponse
s {$sel:nextToken:ListChangeSetsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListChangeSetsResponse)

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

instance Prelude.NFData ListChangeSetsResponse where
  rnf :: ListChangeSetsResponse -> ()
rnf ListChangeSetsResponse' {Int
Maybe [ChangeSetSummaryListItem]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
changeSetSummaryList :: Maybe [ChangeSetSummaryListItem]
$sel:httpStatus:ListChangeSetsResponse' :: ListChangeSetsResponse -> Int
$sel:nextToken:ListChangeSetsResponse' :: ListChangeSetsResponse -> Maybe Text
$sel:changeSetSummaryList:ListChangeSetsResponse' :: ListChangeSetsResponse -> Maybe [ChangeSetSummaryListItem]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ChangeSetSummaryListItem]
changeSetSummaryList
      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 Int
httpStatus