{-# 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.ListComponents
-- 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.ListComponents
  ( -- * Creating a Request
    ListComponents (..),
    newListComponents,

    -- * Request Lenses
    listComponents_byName,
    listComponents_filters,
    listComponents_maxResults,
    listComponents_nextToken,
    listComponents_owner,

    -- * Destructuring the Response
    ListComponentsResponse (..),
    newListComponentsResponse,

    -- * Response Lenses
    listComponentsResponse_componentVersionList,
    listComponentsResponse_nextToken,
    listComponentsResponse_requestId,
    listComponentsResponse_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:/ 'newListComponents' smart constructor.
data ListComponents = ListComponents'
  { -- | Returns the list of component build versions for the specified name.
    ListComponents -> Maybe Bool
byName :: Prelude.Maybe Prelude.Bool,
    -- | Use the following filters to streamline results:
    --
    -- -   @description@
    --
    -- -   @name@
    --
    -- -   @platform@
    --
    -- -   @supportedOsVersion@
    --
    -- -   @type@
    --
    -- -   @version@
    ListComponents -> Maybe (NonEmpty Filter)
filters :: Prelude.Maybe (Prelude.NonEmpty Filter),
    -- | The maximum items to return in a request.
    ListComponents -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A token to specify where to start paginating. This is the NextToken from
    -- a previously truncated response.
    ListComponents -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The owner defines which components you want to list. By default, this
    -- request will only show components owned by your account. You can use
    -- this field to specify if you want to view components owned by yourself,
    -- by Amazon, or those components that have been shared with you by other
    -- customers.
    ListComponents -> Maybe Ownership
owner :: Prelude.Maybe Ownership
  }
  deriving (ListComponents -> ListComponents -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListComponents -> ListComponents -> Bool
$c/= :: ListComponents -> ListComponents -> Bool
== :: ListComponents -> ListComponents -> Bool
$c== :: ListComponents -> ListComponents -> Bool
Prelude.Eq, ReadPrec [ListComponents]
ReadPrec ListComponents
Int -> ReadS ListComponents
ReadS [ListComponents]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListComponents]
$creadListPrec :: ReadPrec [ListComponents]
readPrec :: ReadPrec ListComponents
$creadPrec :: ReadPrec ListComponents
readList :: ReadS [ListComponents]
$creadList :: ReadS [ListComponents]
readsPrec :: Int -> ReadS ListComponents
$creadsPrec :: Int -> ReadS ListComponents
Prelude.Read, Int -> ListComponents -> ShowS
[ListComponents] -> ShowS
ListComponents -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListComponents] -> ShowS
$cshowList :: [ListComponents] -> ShowS
show :: ListComponents -> String
$cshow :: ListComponents -> String
showsPrec :: Int -> ListComponents -> ShowS
$cshowsPrec :: Int -> ListComponents -> ShowS
Prelude.Show, forall x. Rep ListComponents x -> ListComponents
forall x. ListComponents -> Rep ListComponents x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListComponents x -> ListComponents
$cfrom :: forall x. ListComponents -> Rep ListComponents x
Prelude.Generic)

-- |
-- Create a value of 'ListComponents' 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:
--
-- 'byName', 'listComponents_byName' - Returns the list of component build versions for the specified name.
--
-- 'filters', 'listComponents_filters' - Use the following filters to streamline results:
--
-- -   @description@
--
-- -   @name@
--
-- -   @platform@
--
-- -   @supportedOsVersion@
--
-- -   @type@
--
-- -   @version@
--
-- 'maxResults', 'listComponents_maxResults' - The maximum items to return in a request.
--
-- 'nextToken', 'listComponents_nextToken' - A token to specify where to start paginating. This is the NextToken from
-- a previously truncated response.
--
-- 'owner', 'listComponents_owner' - The owner defines which components you want to list. By default, this
-- request will only show components owned by your account. You can use
-- this field to specify if you want to view components owned by yourself,
-- by Amazon, or those components that have been shared with you by other
-- customers.
newListComponents ::
  ListComponents
newListComponents :: ListComponents
newListComponents =
  ListComponents'
    { $sel:byName:ListComponents' :: Maybe Bool
byName = forall a. Maybe a
Prelude.Nothing,
      $sel:filters:ListComponents' :: Maybe (NonEmpty Filter)
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListComponents' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListComponents' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:owner:ListComponents' :: Maybe Ownership
owner = forall a. Maybe a
Prelude.Nothing
    }

-- | Returns the list of component build versions for the specified name.
listComponents_byName :: Lens.Lens' ListComponents (Prelude.Maybe Prelude.Bool)
listComponents_byName :: Lens' ListComponents (Maybe Bool)
listComponents_byName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponents' {Maybe Bool
byName :: Maybe Bool
$sel:byName:ListComponents' :: ListComponents -> Maybe Bool
byName} -> Maybe Bool
byName) (\s :: ListComponents
s@ListComponents' {} Maybe Bool
a -> ListComponents
s {$sel:byName:ListComponents' :: Maybe Bool
byName = Maybe Bool
a} :: ListComponents)

-- | Use the following filters to streamline results:
--
-- -   @description@
--
-- -   @name@
--
-- -   @platform@
--
-- -   @supportedOsVersion@
--
-- -   @type@
--
-- -   @version@
listComponents_filters :: Lens.Lens' ListComponents (Prelude.Maybe (Prelude.NonEmpty Filter))
listComponents_filters :: Lens' ListComponents (Maybe (NonEmpty Filter))
listComponents_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponents' {Maybe (NonEmpty Filter)
filters :: Maybe (NonEmpty Filter)
$sel:filters:ListComponents' :: ListComponents -> Maybe (NonEmpty Filter)
filters} -> Maybe (NonEmpty Filter)
filters) (\s :: ListComponents
s@ListComponents' {} Maybe (NonEmpty Filter)
a -> ListComponents
s {$sel:filters:ListComponents' :: Maybe (NonEmpty Filter)
filters = Maybe (NonEmpty Filter)
a} :: ListComponents) 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 items to return in a request.
listComponents_maxResults :: Lens.Lens' ListComponents (Prelude.Maybe Prelude.Natural)
listComponents_maxResults :: Lens' ListComponents (Maybe Natural)
listComponents_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponents' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListComponents' :: ListComponents -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListComponents
s@ListComponents' {} Maybe Natural
a -> ListComponents
s {$sel:maxResults:ListComponents' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListComponents)

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

-- | The owner defines which components you want to list. By default, this
-- request will only show components owned by your account. You can use
-- this field to specify if you want to view components owned by yourself,
-- by Amazon, or those components that have been shared with you by other
-- customers.
listComponents_owner :: Lens.Lens' ListComponents (Prelude.Maybe Ownership)
listComponents_owner :: Lens' ListComponents (Maybe Ownership)
listComponents_owner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponents' {Maybe Ownership
owner :: Maybe Ownership
$sel:owner:ListComponents' :: ListComponents -> Maybe Ownership
owner} -> Maybe Ownership
owner) (\s :: ListComponents
s@ListComponents' {} Maybe Ownership
a -> ListComponents
s {$sel:owner:ListComponents' :: Maybe Ownership
owner = Maybe Ownership
a} :: ListComponents)

instance Core.AWSRequest ListComponents where
  type
    AWSResponse ListComponents =
      ListComponentsResponse
  request :: (Service -> Service) -> ListComponents -> Request ListComponents
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 ListComponents
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListComponents)))
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 [ComponentVersion]
-> Maybe Text -> Maybe Text -> Int -> ListComponentsResponse
ListComponentsResponse'
            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
"componentVersionList"
                            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 ListComponents where
  hashWithSalt :: Int -> ListComponents -> Int
hashWithSalt Int
_salt ListComponents' {Maybe Bool
Maybe Natural
Maybe (NonEmpty Filter)
Maybe Text
Maybe Ownership
owner :: Maybe Ownership
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe (NonEmpty Filter)
byName :: Maybe Bool
$sel:owner:ListComponents' :: ListComponents -> Maybe Ownership
$sel:nextToken:ListComponents' :: ListComponents -> Maybe Text
$sel:maxResults:ListComponents' :: ListComponents -> Maybe Natural
$sel:filters:ListComponents' :: ListComponents -> Maybe (NonEmpty Filter)
$sel:byName:ListComponents' :: ListComponents -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
byName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Filter)
filters
      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 Ownership
owner

instance Prelude.NFData ListComponents where
  rnf :: ListComponents -> ()
rnf ListComponents' {Maybe Bool
Maybe Natural
Maybe (NonEmpty Filter)
Maybe Text
Maybe Ownership
owner :: Maybe Ownership
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe (NonEmpty Filter)
byName :: Maybe Bool
$sel:owner:ListComponents' :: ListComponents -> Maybe Ownership
$sel:nextToken:ListComponents' :: ListComponents -> Maybe Text
$sel:maxResults:ListComponents' :: ListComponents -> Maybe Natural
$sel:filters:ListComponents' :: ListComponents -> Maybe (NonEmpty Filter)
$sel:byName:ListComponents' :: ListComponents -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
byName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Filter)
filters
      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 Ownership
owner

instance Data.ToHeaders ListComponents where
  toHeaders :: ListComponents -> 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 ListComponents where
  toJSON :: ListComponents -> Value
toJSON ListComponents' {Maybe Bool
Maybe Natural
Maybe (NonEmpty Filter)
Maybe Text
Maybe Ownership
owner :: Maybe Ownership
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe (NonEmpty Filter)
byName :: Maybe Bool
$sel:owner:ListComponents' :: ListComponents -> Maybe Ownership
$sel:nextToken:ListComponents' :: ListComponents -> Maybe Text
$sel:maxResults:ListComponents' :: ListComponents -> Maybe Natural
$sel:filters:ListComponents' :: ListComponents -> Maybe (NonEmpty Filter)
$sel:byName:ListComponents' :: ListComponents -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"byName" 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 Bool
byName,
            (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 (NonEmpty 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 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
"owner" 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 Ownership
owner
          ]
      )

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

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

-- | /See:/ 'newListComponentsResponse' smart constructor.
data ListComponentsResponse = ListComponentsResponse'
  { -- | The list of component semantic versions.
    --
    -- 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.
    ListComponentsResponse -> Maybe [ComponentVersion]
componentVersionList :: Prelude.Maybe [ComponentVersion],
    -- | 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.
    ListComponentsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The request ID that uniquely identifies this request.
    ListComponentsResponse -> Maybe Text
requestId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListComponentsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListComponentsResponse -> ListComponentsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListComponentsResponse -> ListComponentsResponse -> Bool
$c/= :: ListComponentsResponse -> ListComponentsResponse -> Bool
== :: ListComponentsResponse -> ListComponentsResponse -> Bool
$c== :: ListComponentsResponse -> ListComponentsResponse -> Bool
Prelude.Eq, ReadPrec [ListComponentsResponse]
ReadPrec ListComponentsResponse
Int -> ReadS ListComponentsResponse
ReadS [ListComponentsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListComponentsResponse]
$creadListPrec :: ReadPrec [ListComponentsResponse]
readPrec :: ReadPrec ListComponentsResponse
$creadPrec :: ReadPrec ListComponentsResponse
readList :: ReadS [ListComponentsResponse]
$creadList :: ReadS [ListComponentsResponse]
readsPrec :: Int -> ReadS ListComponentsResponse
$creadsPrec :: Int -> ReadS ListComponentsResponse
Prelude.Read, Int -> ListComponentsResponse -> ShowS
[ListComponentsResponse] -> ShowS
ListComponentsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListComponentsResponse] -> ShowS
$cshowList :: [ListComponentsResponse] -> ShowS
show :: ListComponentsResponse -> String
$cshow :: ListComponentsResponse -> String
showsPrec :: Int -> ListComponentsResponse -> ShowS
$cshowsPrec :: Int -> ListComponentsResponse -> ShowS
Prelude.Show, forall x. Rep ListComponentsResponse x -> ListComponentsResponse
forall x. ListComponentsResponse -> Rep ListComponentsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListComponentsResponse x -> ListComponentsResponse
$cfrom :: forall x. ListComponentsResponse -> Rep ListComponentsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListComponentsResponse' 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:
--
-- 'componentVersionList', 'listComponentsResponse_componentVersionList' - The list of component semantic versions.
--
-- 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.
--
-- 'nextToken', 'listComponentsResponse_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', 'listComponentsResponse_requestId' - The request ID that uniquely identifies this request.
--
-- 'httpStatus', 'listComponentsResponse_httpStatus' - The response's http status code.
newListComponentsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListComponentsResponse
newListComponentsResponse :: Int -> ListComponentsResponse
newListComponentsResponse Int
pHttpStatus_ =
  ListComponentsResponse'
    { $sel:componentVersionList:ListComponentsResponse' :: Maybe [ComponentVersion]
componentVersionList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListComponentsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:requestId:ListComponentsResponse' :: Maybe Text
requestId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListComponentsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of component semantic versions.
--
-- 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.
listComponentsResponse_componentVersionList :: Lens.Lens' ListComponentsResponse (Prelude.Maybe [ComponentVersion])
listComponentsResponse_componentVersionList :: Lens' ListComponentsResponse (Maybe [ComponentVersion])
listComponentsResponse_componentVersionList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponentsResponse' {Maybe [ComponentVersion]
componentVersionList :: Maybe [ComponentVersion]
$sel:componentVersionList:ListComponentsResponse' :: ListComponentsResponse -> Maybe [ComponentVersion]
componentVersionList} -> Maybe [ComponentVersion]
componentVersionList) (\s :: ListComponentsResponse
s@ListComponentsResponse' {} Maybe [ComponentVersion]
a -> ListComponentsResponse
s {$sel:componentVersionList:ListComponentsResponse' :: Maybe [ComponentVersion]
componentVersionList = Maybe [ComponentVersion]
a} :: ListComponentsResponse) 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.
listComponentsResponse_nextToken :: Lens.Lens' ListComponentsResponse (Prelude.Maybe Prelude.Text)
listComponentsResponse_nextToken :: Lens' ListComponentsResponse (Maybe Text)
listComponentsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListComponentsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListComponentsResponse' :: ListComponentsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListComponentsResponse
s@ListComponentsResponse' {} Maybe Text
a -> ListComponentsResponse
s {$sel:nextToken:ListComponentsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListComponentsResponse)

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

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

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