{-# 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.ImageBuilder.ListComponentBuildVersions
-- 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 component build versions for the specified semantic
-- version.
--
-- The semantic version has four nodes:
-- \<major>.\<minor>.\<patch>\/\<build>. You can assign values for the
-- first three, and can filter on all of them.
--
-- __Filtering:__ With semantic versioning, you have the flexibility to use
-- wildcards (x) to specify the most recent versions or nodes when
-- selecting the base image or components for your recipe. When you use a
-- wildcard in any node, all nodes to the right of the first wildcard must
-- also be wildcards.
module Amazonka.ImageBuilder.ListComponentBuildVersions
  ( -- * Creating a Request
    ListComponentBuildVersions (..),
    newListComponentBuildVersions,

    -- * Request Lenses
    listComponentBuildVersions_maxResults,
    listComponentBuildVersions_nextToken,
    listComponentBuildVersions_componentVersionArn,

    -- * Destructuring the Response
    ListComponentBuildVersionsResponse (..),
    newListComponentBuildVersionsResponse,

    -- * Response Lenses
    listComponentBuildVersionsResponse_componentSummaryList,
    listComponentBuildVersionsResponse_nextToken,
    listComponentBuildVersionsResponse_requestId,
    listComponentBuildVersionsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListComponentBuildVersions' smart constructor.
data ListComponentBuildVersions = ListComponentBuildVersions'
  { -- | The maximum items to return in a request.
    ListComponentBuildVersions -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A token to specify where to start paginating. This is the NextToken from
    -- a previously truncated response.
    ListComponentBuildVersions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The component version Amazon Resource Name (ARN) whose versions you want
    -- to list.
    ListComponentBuildVersions -> Text
componentVersionArn :: Prelude.Text
  }
  deriving (ListComponentBuildVersions -> ListComponentBuildVersions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListComponentBuildVersions -> ListComponentBuildVersions -> Bool
$c/= :: ListComponentBuildVersions -> ListComponentBuildVersions -> Bool
== :: ListComponentBuildVersions -> ListComponentBuildVersions -> Bool
$c== :: ListComponentBuildVersions -> ListComponentBuildVersions -> Bool
Prelude.Eq, ReadPrec [ListComponentBuildVersions]
ReadPrec ListComponentBuildVersions
Int -> ReadS ListComponentBuildVersions
ReadS [ListComponentBuildVersions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListComponentBuildVersions]
$creadListPrec :: ReadPrec [ListComponentBuildVersions]
readPrec :: ReadPrec ListComponentBuildVersions
$creadPrec :: ReadPrec ListComponentBuildVersions
readList :: ReadS [ListComponentBuildVersions]
$creadList :: ReadS [ListComponentBuildVersions]
readsPrec :: Int -> ReadS ListComponentBuildVersions
$creadsPrec :: Int -> ReadS ListComponentBuildVersions
Prelude.Read, Int -> ListComponentBuildVersions -> ShowS
[ListComponentBuildVersions] -> ShowS
ListComponentBuildVersions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListComponentBuildVersions] -> ShowS
$cshowList :: [ListComponentBuildVersions] -> ShowS
show :: ListComponentBuildVersions -> String
$cshow :: ListComponentBuildVersions -> String
showsPrec :: Int -> ListComponentBuildVersions -> ShowS
$cshowsPrec :: Int -> ListComponentBuildVersions -> ShowS
Prelude.Show, forall x.
Rep ListComponentBuildVersions x -> ListComponentBuildVersions
forall x.
ListComponentBuildVersions -> Rep ListComponentBuildVersions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListComponentBuildVersions x -> ListComponentBuildVersions
$cfrom :: forall x.
ListComponentBuildVersions -> Rep ListComponentBuildVersions x
Prelude.Generic)

-- |
-- Create a value of 'ListComponentBuildVersions' 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', 'listComponentBuildVersions_maxResults' - The maximum items to return in a request.
--
-- 'nextToken', 'listComponentBuildVersions_nextToken' - A token to specify where to start paginating. This is the NextToken from
-- a previously truncated response.
--
-- 'componentVersionArn', 'listComponentBuildVersions_componentVersionArn' - The component version Amazon Resource Name (ARN) whose versions you want
-- to list.
newListComponentBuildVersions ::
  -- | 'componentVersionArn'
  Prelude.Text ->
  ListComponentBuildVersions
newListComponentBuildVersions :: Text -> ListComponentBuildVersions
newListComponentBuildVersions Text
pComponentVersionArn_ =
  ListComponentBuildVersions'
    { $sel:maxResults:ListComponentBuildVersions' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListComponentBuildVersions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:componentVersionArn:ListComponentBuildVersions' :: Text
componentVersionArn = Text
pComponentVersionArn_
    }

-- | The maximum items to return in a request.
listComponentBuildVersions_maxResults :: Lens.Lens' ListComponentBuildVersions (Prelude.Maybe Prelude.Natural)
listComponentBuildVersions_maxResults :: Lens' ListComponentBuildVersions (Maybe Natural)
listComponentBuildVersions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponentBuildVersions' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListComponentBuildVersions' :: ListComponentBuildVersions -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListComponentBuildVersions
s@ListComponentBuildVersions' {} Maybe Natural
a -> ListComponentBuildVersions
s {$sel:maxResults:ListComponentBuildVersions' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListComponentBuildVersions)

-- | A token to specify where to start paginating. This is the NextToken from
-- a previously truncated response.
listComponentBuildVersions_nextToken :: Lens.Lens' ListComponentBuildVersions (Prelude.Maybe Prelude.Text)
listComponentBuildVersions_nextToken :: Lens' ListComponentBuildVersions (Maybe Text)
listComponentBuildVersions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponentBuildVersions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListComponentBuildVersions' :: ListComponentBuildVersions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListComponentBuildVersions
s@ListComponentBuildVersions' {} Maybe Text
a -> ListComponentBuildVersions
s {$sel:nextToken:ListComponentBuildVersions' :: Maybe Text
nextToken = Maybe Text
a} :: ListComponentBuildVersions)

-- | The component version Amazon Resource Name (ARN) whose versions you want
-- to list.
listComponentBuildVersions_componentVersionArn :: Lens.Lens' ListComponentBuildVersions Prelude.Text
listComponentBuildVersions_componentVersionArn :: Lens' ListComponentBuildVersions Text
listComponentBuildVersions_componentVersionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponentBuildVersions' {Text
componentVersionArn :: Text
$sel:componentVersionArn:ListComponentBuildVersions' :: ListComponentBuildVersions -> Text
componentVersionArn} -> Text
componentVersionArn) (\s :: ListComponentBuildVersions
s@ListComponentBuildVersions' {} Text
a -> ListComponentBuildVersions
s {$sel:componentVersionArn:ListComponentBuildVersions' :: Text
componentVersionArn = Text
a} :: ListComponentBuildVersions)

instance Core.AWSRequest ListComponentBuildVersions where
  type
    AWSResponse ListComponentBuildVersions =
      ListComponentBuildVersionsResponse
  request :: (Service -> Service)
-> ListComponentBuildVersions -> Request ListComponentBuildVersions
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 ListComponentBuildVersions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListComponentBuildVersions)))
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 [ComponentSummary]
-> Maybe Text
-> Maybe Text
-> Int
-> ListComponentBuildVersionsResponse
ListComponentBuildVersionsResponse'
            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
"componentSummaryList"
                            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"requestId")
            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 ListComponentBuildVersions where
  hashWithSalt :: Int -> ListComponentBuildVersions -> Int
hashWithSalt Int
_salt ListComponentBuildVersions' {Maybe Natural
Maybe Text
Text
componentVersionArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:componentVersionArn:ListComponentBuildVersions' :: ListComponentBuildVersions -> Text
$sel:nextToken:ListComponentBuildVersions' :: ListComponentBuildVersions -> Maybe Text
$sel:maxResults:ListComponentBuildVersions' :: ListComponentBuildVersions -> 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
componentVersionArn

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

instance Data.ToHeaders ListComponentBuildVersions where
  toHeaders :: ListComponentBuildVersions -> 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 ListComponentBuildVersions where
  toJSON :: ListComponentBuildVersions -> Value
toJSON ListComponentBuildVersions' {Maybe Natural
Maybe Text
Text
componentVersionArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:componentVersionArn:ListComponentBuildVersions' :: ListComponentBuildVersions -> Text
$sel:nextToken:ListComponentBuildVersions' :: ListComponentBuildVersions -> Maybe Text
$sel:maxResults:ListComponentBuildVersions' :: ListComponentBuildVersions -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"componentVersionArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
componentVersionArn)
          ]
      )

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

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

-- | /See:/ 'newListComponentBuildVersionsResponse' smart constructor.
data ListComponentBuildVersionsResponse = ListComponentBuildVersionsResponse'
  { -- | The list of component summaries for the specified semantic version.
    ListComponentBuildVersionsResponse -> Maybe [ComponentSummary]
componentSummaryList :: Prelude.Maybe [ComponentSummary],
    -- | The next token used for paginated responses. When this is not empty,
    -- there are additional elements that the service has not included in this
    -- request. Use this token with the next request to retrieve additional
    -- objects.
    ListComponentBuildVersionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The request ID that uniquely identifies this request.
    ListComponentBuildVersionsResponse -> Maybe Text
requestId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListComponentBuildVersionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListComponentBuildVersionsResponse
-> ListComponentBuildVersionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListComponentBuildVersionsResponse
-> ListComponentBuildVersionsResponse -> Bool
$c/= :: ListComponentBuildVersionsResponse
-> ListComponentBuildVersionsResponse -> Bool
== :: ListComponentBuildVersionsResponse
-> ListComponentBuildVersionsResponse -> Bool
$c== :: ListComponentBuildVersionsResponse
-> ListComponentBuildVersionsResponse -> Bool
Prelude.Eq, ReadPrec [ListComponentBuildVersionsResponse]
ReadPrec ListComponentBuildVersionsResponse
Int -> ReadS ListComponentBuildVersionsResponse
ReadS [ListComponentBuildVersionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListComponentBuildVersionsResponse]
$creadListPrec :: ReadPrec [ListComponentBuildVersionsResponse]
readPrec :: ReadPrec ListComponentBuildVersionsResponse
$creadPrec :: ReadPrec ListComponentBuildVersionsResponse
readList :: ReadS [ListComponentBuildVersionsResponse]
$creadList :: ReadS [ListComponentBuildVersionsResponse]
readsPrec :: Int -> ReadS ListComponentBuildVersionsResponse
$creadsPrec :: Int -> ReadS ListComponentBuildVersionsResponse
Prelude.Read, Int -> ListComponentBuildVersionsResponse -> ShowS
[ListComponentBuildVersionsResponse] -> ShowS
ListComponentBuildVersionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListComponentBuildVersionsResponse] -> ShowS
$cshowList :: [ListComponentBuildVersionsResponse] -> ShowS
show :: ListComponentBuildVersionsResponse -> String
$cshow :: ListComponentBuildVersionsResponse -> String
showsPrec :: Int -> ListComponentBuildVersionsResponse -> ShowS
$cshowsPrec :: Int -> ListComponentBuildVersionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListComponentBuildVersionsResponse x
-> ListComponentBuildVersionsResponse
forall x.
ListComponentBuildVersionsResponse
-> Rep ListComponentBuildVersionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListComponentBuildVersionsResponse x
-> ListComponentBuildVersionsResponse
$cfrom :: forall x.
ListComponentBuildVersionsResponse
-> Rep ListComponentBuildVersionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListComponentBuildVersionsResponse' 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:
--
-- 'componentSummaryList', 'listComponentBuildVersionsResponse_componentSummaryList' - The list of component summaries for the specified semantic version.
--
-- 'nextToken', 'listComponentBuildVersionsResponse_nextToken' - The next token used for paginated responses. When this is not empty,
-- there are additional elements that the service has not included in this
-- request. Use this token with the next request to retrieve additional
-- objects.
--
-- 'requestId', 'listComponentBuildVersionsResponse_requestId' - The request ID that uniquely identifies this request.
--
-- 'httpStatus', 'listComponentBuildVersionsResponse_httpStatus' - The response's http status code.
newListComponentBuildVersionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListComponentBuildVersionsResponse
newListComponentBuildVersionsResponse :: Int -> ListComponentBuildVersionsResponse
newListComponentBuildVersionsResponse Int
pHttpStatus_ =
  ListComponentBuildVersionsResponse'
    { $sel:componentSummaryList:ListComponentBuildVersionsResponse' :: Maybe [ComponentSummary]
componentSummaryList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListComponentBuildVersionsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:requestId:ListComponentBuildVersionsResponse' :: Maybe Text
requestId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListComponentBuildVersionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of component summaries for the specified semantic version.
listComponentBuildVersionsResponse_componentSummaryList :: Lens.Lens' ListComponentBuildVersionsResponse (Prelude.Maybe [ComponentSummary])
listComponentBuildVersionsResponse_componentSummaryList :: Lens' ListComponentBuildVersionsResponse (Maybe [ComponentSummary])
listComponentBuildVersionsResponse_componentSummaryList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponentBuildVersionsResponse' {Maybe [ComponentSummary]
componentSummaryList :: Maybe [ComponentSummary]
$sel:componentSummaryList:ListComponentBuildVersionsResponse' :: ListComponentBuildVersionsResponse -> Maybe [ComponentSummary]
componentSummaryList} -> Maybe [ComponentSummary]
componentSummaryList) (\s :: ListComponentBuildVersionsResponse
s@ListComponentBuildVersionsResponse' {} Maybe [ComponentSummary]
a -> ListComponentBuildVersionsResponse
s {$sel:componentSummaryList:ListComponentBuildVersionsResponse' :: Maybe [ComponentSummary]
componentSummaryList = Maybe [ComponentSummary]
a} :: ListComponentBuildVersionsResponse) 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 next token used for paginated responses. When this is not empty,
-- there are additional elements that the service has not included in this
-- request. Use this token with the next request to retrieve additional
-- objects.
listComponentBuildVersionsResponse_nextToken :: Lens.Lens' ListComponentBuildVersionsResponse (Prelude.Maybe Prelude.Text)
listComponentBuildVersionsResponse_nextToken :: Lens' ListComponentBuildVersionsResponse (Maybe Text)
listComponentBuildVersionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponentBuildVersionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListComponentBuildVersionsResponse' :: ListComponentBuildVersionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListComponentBuildVersionsResponse
s@ListComponentBuildVersionsResponse' {} Maybe Text
a -> ListComponentBuildVersionsResponse
s {$sel:nextToken:ListComponentBuildVersionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListComponentBuildVersionsResponse)

-- | The request ID that uniquely identifies this request.
listComponentBuildVersionsResponse_requestId :: Lens.Lens' ListComponentBuildVersionsResponse (Prelude.Maybe Prelude.Text)
listComponentBuildVersionsResponse_requestId :: Lens' ListComponentBuildVersionsResponse (Maybe Text)
listComponentBuildVersionsResponse_requestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponentBuildVersionsResponse' {Maybe Text
requestId :: Maybe Text
$sel:requestId:ListComponentBuildVersionsResponse' :: ListComponentBuildVersionsResponse -> Maybe Text
requestId} -> Maybe Text
requestId) (\s :: ListComponentBuildVersionsResponse
s@ListComponentBuildVersionsResponse' {} Maybe Text
a -> ListComponentBuildVersionsResponse
s {$sel:requestId:ListComponentBuildVersionsResponse' :: Maybe Text
requestId = Maybe Text
a} :: ListComponentBuildVersionsResponse)

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

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