{-# 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.EKS.ListAddons
-- 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 available add-ons.
--
-- This operation returns paginated results.
module Amazonka.EKS.ListAddons
  ( -- * Creating a Request
    ListAddons (..),
    newListAddons,

    -- * Request Lenses
    listAddons_maxResults,
    listAddons_nextToken,
    listAddons_clusterName,

    -- * Destructuring the Response
    ListAddonsResponse (..),
    newListAddonsResponse,

    -- * Response Lenses
    listAddonsResponse_addons,
    listAddonsResponse_nextToken,
    listAddonsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListAddons' smart constructor.
data ListAddons = ListAddons'
  { -- | The maximum number of add-on results returned by @ListAddonsRequest@ in
    -- paginated output. When you use this parameter, @ListAddonsRequest@
    -- returns only @maxResults@ results in a single page along with a
    -- @nextToken@ response element. You can see the remaining results of the
    -- initial request by sending another @ListAddonsRequest@ request with the
    -- returned @nextToken@ value. This value can be between 1 and 100. If you
    -- don\'t use this parameter, @ListAddonsRequest@ returns up to 100 results
    -- and a @nextToken@ value, if applicable.
    ListAddons -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The @nextToken@ value returned from a previous paginated
    -- @ListAddonsRequest@ where @maxResults@ was used and the results exceeded
    -- the value of that parameter. Pagination continues from the end of the
    -- previous results that returned the @nextToken@ value.
    --
    -- This token should be treated as an opaque identifier that is used only
    -- to retrieve the next items in a list and not for other programmatic
    -- purposes.
    ListAddons -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the cluster.
    ListAddons -> Text
clusterName :: Prelude.Text
  }
  deriving (ListAddons -> ListAddons -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAddons -> ListAddons -> Bool
$c/= :: ListAddons -> ListAddons -> Bool
== :: ListAddons -> ListAddons -> Bool
$c== :: ListAddons -> ListAddons -> Bool
Prelude.Eq, ReadPrec [ListAddons]
ReadPrec ListAddons
Int -> ReadS ListAddons
ReadS [ListAddons]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAddons]
$creadListPrec :: ReadPrec [ListAddons]
readPrec :: ReadPrec ListAddons
$creadPrec :: ReadPrec ListAddons
readList :: ReadS [ListAddons]
$creadList :: ReadS [ListAddons]
readsPrec :: Int -> ReadS ListAddons
$creadsPrec :: Int -> ReadS ListAddons
Prelude.Read, Int -> ListAddons -> ShowS
[ListAddons] -> ShowS
ListAddons -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAddons] -> ShowS
$cshowList :: [ListAddons] -> ShowS
show :: ListAddons -> String
$cshow :: ListAddons -> String
showsPrec :: Int -> ListAddons -> ShowS
$cshowsPrec :: Int -> ListAddons -> ShowS
Prelude.Show, forall x. Rep ListAddons x -> ListAddons
forall x. ListAddons -> Rep ListAddons x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAddons x -> ListAddons
$cfrom :: forall x. ListAddons -> Rep ListAddons x
Prelude.Generic)

-- |
-- Create a value of 'ListAddons' 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:
--
-- 'maxResults', 'listAddons_maxResults' - The maximum number of add-on results returned by @ListAddonsRequest@ in
-- paginated output. When you use this parameter, @ListAddonsRequest@
-- returns only @maxResults@ results in a single page along with a
-- @nextToken@ response element. You can see the remaining results of the
-- initial request by sending another @ListAddonsRequest@ request with the
-- returned @nextToken@ value. This value can be between 1 and 100. If you
-- don\'t use this parameter, @ListAddonsRequest@ returns up to 100 results
-- and a @nextToken@ value, if applicable.
--
-- 'nextToken', 'listAddons_nextToken' - The @nextToken@ value returned from a previous paginated
-- @ListAddonsRequest@ where @maxResults@ was used and the results exceeded
-- the value of that parameter. Pagination continues from the end of the
-- previous results that returned the @nextToken@ value.
--
-- This token should be treated as an opaque identifier that is used only
-- to retrieve the next items in a list and not for other programmatic
-- purposes.
--
-- 'clusterName', 'listAddons_clusterName' - The name of the cluster.
newListAddons ::
  -- | 'clusterName'
  Prelude.Text ->
  ListAddons
newListAddons :: Text -> ListAddons
newListAddons Text
pClusterName_ =
  ListAddons'
    { $sel:maxResults:ListAddons' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAddons' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterName:ListAddons' :: Text
clusterName = Text
pClusterName_
    }

-- | The maximum number of add-on results returned by @ListAddonsRequest@ in
-- paginated output. When you use this parameter, @ListAddonsRequest@
-- returns only @maxResults@ results in a single page along with a
-- @nextToken@ response element. You can see the remaining results of the
-- initial request by sending another @ListAddonsRequest@ request with the
-- returned @nextToken@ value. This value can be between 1 and 100. If you
-- don\'t use this parameter, @ListAddonsRequest@ returns up to 100 results
-- and a @nextToken@ value, if applicable.
listAddons_maxResults :: Lens.Lens' ListAddons (Prelude.Maybe Prelude.Natural)
listAddons_maxResults :: Lens' ListAddons (Maybe Natural)
listAddons_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAddons' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListAddons' :: ListAddons -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListAddons
s@ListAddons' {} Maybe Natural
a -> ListAddons
s {$sel:maxResults:ListAddons' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListAddons)

-- | The @nextToken@ value returned from a previous paginated
-- @ListAddonsRequest@ where @maxResults@ was used and the results exceeded
-- the value of that parameter. Pagination continues from the end of the
-- previous results that returned the @nextToken@ value.
--
-- This token should be treated as an opaque identifier that is used only
-- to retrieve the next items in a list and not for other programmatic
-- purposes.
listAddons_nextToken :: Lens.Lens' ListAddons (Prelude.Maybe Prelude.Text)
listAddons_nextToken :: Lens' ListAddons (Maybe Text)
listAddons_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAddons' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAddons' :: ListAddons -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAddons
s@ListAddons' {} Maybe Text
a -> ListAddons
s {$sel:nextToken:ListAddons' :: Maybe Text
nextToken = Maybe Text
a} :: ListAddons)

-- | The name of the cluster.
listAddons_clusterName :: Lens.Lens' ListAddons Prelude.Text
listAddons_clusterName :: Lens' ListAddons Text
listAddons_clusterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAddons' {Text
clusterName :: Text
$sel:clusterName:ListAddons' :: ListAddons -> Text
clusterName} -> Text
clusterName) (\s :: ListAddons
s@ListAddons' {} Text
a -> ListAddons
s {$sel:clusterName:ListAddons' :: Text
clusterName = Text
a} :: ListAddons)

instance Core.AWSPager ListAddons where
  page :: ListAddons -> AWSResponse ListAddons -> Maybe ListAddons
page ListAddons
rq AWSResponse ListAddons
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListAddons
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAddonsResponse (Maybe Text)
listAddonsResponse_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 ListAddons
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAddonsResponse (Maybe [Text])
listAddonsResponse_addons
            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.$ ListAddons
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListAddons (Maybe Text)
listAddons_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListAddons
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAddonsResponse (Maybe Text)
listAddonsResponse_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 ListAddons where
  type AWSResponse ListAddons = ListAddonsResponse
  request :: (Service -> Service) -> ListAddons -> Request ListAddons
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 ListAddons
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListAddons)))
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 Text -> Int -> ListAddonsResponse
ListAddonsResponse'
            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
"addons" 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 ListAddons where
  hashWithSalt :: Int -> ListAddons -> Int
hashWithSalt Int
_salt ListAddons' {Maybe Natural
Maybe Text
Text
clusterName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:clusterName:ListAddons' :: ListAddons -> Text
$sel:nextToken:ListAddons' :: ListAddons -> Maybe Text
$sel:maxResults:ListAddons' :: ListAddons -> Maybe Natural
..} =
    Int
_salt
      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` Text
clusterName

instance Prelude.NFData ListAddons where
  rnf :: ListAddons -> ()
rnf ListAddons' {Maybe Natural
Maybe Text
Text
clusterName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:clusterName:ListAddons' :: ListAddons -> Text
$sel:nextToken:ListAddons' :: ListAddons -> Maybe Text
$sel:maxResults:ListAddons' :: ListAddons -> Maybe Natural
..} =
    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 Text
clusterName

instance Data.ToHeaders ListAddons where
  toHeaders :: ListAddons -> 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 ListAddons where
  toPath :: ListAddons -> ByteString
toPath ListAddons' {Maybe Natural
Maybe Text
Text
clusterName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:clusterName:ListAddons' :: ListAddons -> Text
$sel:nextToken:ListAddons' :: ListAddons -> Maybe Text
$sel:maxResults:ListAddons' :: ListAddons -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/clusters/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
clusterName, ByteString
"/addons"]

instance Data.ToQuery ListAddons where
  toQuery :: ListAddons -> QueryString
toQuery ListAddons' {Maybe Natural
Maybe Text
Text
clusterName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:clusterName:ListAddons' :: ListAddons -> Text
$sel:nextToken:ListAddons' :: ListAddons -> Maybe Text
$sel:maxResults:ListAddons' :: ListAddons -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newListAddonsResponse' smart constructor.
data ListAddonsResponse = ListAddonsResponse'
  { -- | A list of available add-ons.
    ListAddonsResponse -> Maybe [Text]
addons :: Prelude.Maybe [Prelude.Text],
    -- | The @nextToken@ value returned from a previous paginated
    -- @ListAddonsResponse@ where @maxResults@ was used and the results
    -- exceeded the value of that parameter. Pagination continues from the end
    -- of the previous results that returned the @nextToken@ value.
    --
    -- This token should be treated as an opaque identifier that is used only
    -- to retrieve the next items in a list and not for other programmatic
    -- purposes.
    ListAddonsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAddonsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListAddonsResponse -> ListAddonsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAddonsResponse -> ListAddonsResponse -> Bool
$c/= :: ListAddonsResponse -> ListAddonsResponse -> Bool
== :: ListAddonsResponse -> ListAddonsResponse -> Bool
$c== :: ListAddonsResponse -> ListAddonsResponse -> Bool
Prelude.Eq, ReadPrec [ListAddonsResponse]
ReadPrec ListAddonsResponse
Int -> ReadS ListAddonsResponse
ReadS [ListAddonsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAddonsResponse]
$creadListPrec :: ReadPrec [ListAddonsResponse]
readPrec :: ReadPrec ListAddonsResponse
$creadPrec :: ReadPrec ListAddonsResponse
readList :: ReadS [ListAddonsResponse]
$creadList :: ReadS [ListAddonsResponse]
readsPrec :: Int -> ReadS ListAddonsResponse
$creadsPrec :: Int -> ReadS ListAddonsResponse
Prelude.Read, Int -> ListAddonsResponse -> ShowS
[ListAddonsResponse] -> ShowS
ListAddonsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAddonsResponse] -> ShowS
$cshowList :: [ListAddonsResponse] -> ShowS
show :: ListAddonsResponse -> String
$cshow :: ListAddonsResponse -> String
showsPrec :: Int -> ListAddonsResponse -> ShowS
$cshowsPrec :: Int -> ListAddonsResponse -> ShowS
Prelude.Show, forall x. Rep ListAddonsResponse x -> ListAddonsResponse
forall x. ListAddonsResponse -> Rep ListAddonsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAddonsResponse x -> ListAddonsResponse
$cfrom :: forall x. ListAddonsResponse -> Rep ListAddonsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAddonsResponse' 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:
--
-- 'addons', 'listAddonsResponse_addons' - A list of available add-ons.
--
-- 'nextToken', 'listAddonsResponse_nextToken' - The @nextToken@ value returned from a previous paginated
-- @ListAddonsResponse@ where @maxResults@ was used and the results
-- exceeded the value of that parameter. Pagination continues from the end
-- of the previous results that returned the @nextToken@ value.
--
-- This token should be treated as an opaque identifier that is used only
-- to retrieve the next items in a list and not for other programmatic
-- purposes.
--
-- 'httpStatus', 'listAddonsResponse_httpStatus' - The response's http status code.
newListAddonsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAddonsResponse
newListAddonsResponse :: Int -> ListAddonsResponse
newListAddonsResponse Int
pHttpStatus_ =
  ListAddonsResponse'
    { $sel:addons:ListAddonsResponse' :: Maybe [Text]
addons = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAddonsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAddonsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of available add-ons.
listAddonsResponse_addons :: Lens.Lens' ListAddonsResponse (Prelude.Maybe [Prelude.Text])
listAddonsResponse_addons :: Lens' ListAddonsResponse (Maybe [Text])
listAddonsResponse_addons = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAddonsResponse' {Maybe [Text]
addons :: Maybe [Text]
$sel:addons:ListAddonsResponse' :: ListAddonsResponse -> Maybe [Text]
addons} -> Maybe [Text]
addons) (\s :: ListAddonsResponse
s@ListAddonsResponse' {} Maybe [Text]
a -> ListAddonsResponse
s {$sel:addons:ListAddonsResponse' :: Maybe [Text]
addons = Maybe [Text]
a} :: ListAddonsResponse) 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 @nextToken@ value returned from a previous paginated
-- @ListAddonsResponse@ where @maxResults@ was used and the results
-- exceeded the value of that parameter. Pagination continues from the end
-- of the previous results that returned the @nextToken@ value.
--
-- This token should be treated as an opaque identifier that is used only
-- to retrieve the next items in a list and not for other programmatic
-- purposes.
listAddonsResponse_nextToken :: Lens.Lens' ListAddonsResponse (Prelude.Maybe Prelude.Text)
listAddonsResponse_nextToken :: Lens' ListAddonsResponse (Maybe Text)
listAddonsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAddonsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAddonsResponse' :: ListAddonsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAddonsResponse
s@ListAddonsResponse' {} Maybe Text
a -> ListAddonsResponse
s {$sel:nextToken:ListAddonsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAddonsResponse)

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

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