{-# 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.ECR.ListImages
-- 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 all the image IDs for the specified repository.
--
-- You can filter images based on whether or not they are tagged by using
-- the @tagStatus@ filter and specifying either @TAGGED@, @UNTAGGED@ or
-- @ANY@. For example, you can filter your results to return only
-- @UNTAGGED@ images and then pipe that result to a BatchDeleteImage
-- operation to delete them. Or, you can filter your results to return only
-- @TAGGED@ images to list all of the tags in your repository.
--
-- This operation returns paginated results.
module Amazonka.ECR.ListImages
  ( -- * Creating a Request
    ListImages (..),
    newListImages,

    -- * Request Lenses
    listImages_filter,
    listImages_maxResults,
    listImages_nextToken,
    listImages_registryId,
    listImages_repositoryName,

    -- * Destructuring the Response
    ListImagesResponse (..),
    newListImagesResponse,

    -- * Response Lenses
    listImagesResponse_imageIds,
    listImagesResponse_nextToken,
    listImagesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListImages' smart constructor.
data ListImages = ListImages'
  { -- | The filter key and value with which to filter your @ListImages@ results.
    ListImages -> Maybe ListImagesFilter
filter' :: Prelude.Maybe ListImagesFilter,
    -- | The maximum number of image results returned by @ListImages@ in
    -- paginated output. When this parameter is used, @ListImages@ only returns
    -- @maxResults@ results in a single page along with a @nextToken@ response
    -- element. The remaining results of the initial request can be seen by
    -- sending another @ListImages@ request with the returned @nextToken@
    -- value. This value can be between 1 and 1000. If this parameter is not
    -- used, then @ListImages@ returns up to 100 results and a @nextToken@
    -- value, if applicable.
    ListImages -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The @nextToken@ value returned from a previous paginated @ListImages@
    -- request 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 value is @null@ when
    -- there are no more results to return.
    --
    -- This token should be treated as an opaque identifier that is only used
    -- to retrieve the next items in a list and not for other programmatic
    -- purposes.
    ListImages -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account ID associated with the registry that
    -- contains the repository in which to list images. If you do not specify a
    -- registry, the default registry is assumed.
    ListImages -> Maybe Text
registryId :: Prelude.Maybe Prelude.Text,
    -- | The repository with image IDs to be listed.
    ListImages -> Text
repositoryName :: Prelude.Text
  }
  deriving (ListImages -> ListImages -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListImages -> ListImages -> Bool
$c/= :: ListImages -> ListImages -> Bool
== :: ListImages -> ListImages -> Bool
$c== :: ListImages -> ListImages -> Bool
Prelude.Eq, ReadPrec [ListImages]
ReadPrec ListImages
Int -> ReadS ListImages
ReadS [ListImages]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListImages]
$creadListPrec :: ReadPrec [ListImages]
readPrec :: ReadPrec ListImages
$creadPrec :: ReadPrec ListImages
readList :: ReadS [ListImages]
$creadList :: ReadS [ListImages]
readsPrec :: Int -> ReadS ListImages
$creadsPrec :: Int -> ReadS ListImages
Prelude.Read, Int -> ListImages -> ShowS
[ListImages] -> ShowS
ListImages -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListImages] -> ShowS
$cshowList :: [ListImages] -> ShowS
show :: ListImages -> String
$cshow :: ListImages -> String
showsPrec :: Int -> ListImages -> ShowS
$cshowsPrec :: Int -> ListImages -> ShowS
Prelude.Show, forall x. Rep ListImages x -> ListImages
forall x. ListImages -> Rep ListImages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListImages x -> ListImages
$cfrom :: forall x. ListImages -> Rep ListImages x
Prelude.Generic)

-- |
-- Create a value of 'ListImages' 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:
--
-- 'filter'', 'listImages_filter' - The filter key and value with which to filter your @ListImages@ results.
--
-- 'maxResults', 'listImages_maxResults' - The maximum number of image results returned by @ListImages@ in
-- paginated output. When this parameter is used, @ListImages@ only returns
-- @maxResults@ results in a single page along with a @nextToken@ response
-- element. The remaining results of the initial request can be seen by
-- sending another @ListImages@ request with the returned @nextToken@
-- value. This value can be between 1 and 1000. If this parameter is not
-- used, then @ListImages@ returns up to 100 results and a @nextToken@
-- value, if applicable.
--
-- 'nextToken', 'listImages_nextToken' - The @nextToken@ value returned from a previous paginated @ListImages@
-- request 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 value is @null@ when
-- there are no more results to return.
--
-- This token should be treated as an opaque identifier that is only used
-- to retrieve the next items in a list and not for other programmatic
-- purposes.
--
-- 'registryId', 'listImages_registryId' - The Amazon Web Services account ID associated with the registry that
-- contains the repository in which to list images. If you do not specify a
-- registry, the default registry is assumed.
--
-- 'repositoryName', 'listImages_repositoryName' - The repository with image IDs to be listed.
newListImages ::
  -- | 'repositoryName'
  Prelude.Text ->
  ListImages
newListImages :: Text -> ListImages
newListImages Text
pRepositoryName_ =
  ListImages'
    { $sel:filter':ListImages' :: Maybe ListImagesFilter
filter' = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListImages' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListImages' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:registryId:ListImages' :: Maybe Text
registryId = forall a. Maybe a
Prelude.Nothing,
      $sel:repositoryName:ListImages' :: Text
repositoryName = Text
pRepositoryName_
    }

-- | The filter key and value with which to filter your @ListImages@ results.
listImages_filter :: Lens.Lens' ListImages (Prelude.Maybe ListImagesFilter)
listImages_filter :: Lens' ListImages (Maybe ListImagesFilter)
listImages_filter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImages' {Maybe ListImagesFilter
filter' :: Maybe ListImagesFilter
$sel:filter':ListImages' :: ListImages -> Maybe ListImagesFilter
filter'} -> Maybe ListImagesFilter
filter') (\s :: ListImages
s@ListImages' {} Maybe ListImagesFilter
a -> ListImages
s {$sel:filter':ListImages' :: Maybe ListImagesFilter
filter' = Maybe ListImagesFilter
a} :: ListImages)

-- | The maximum number of image results returned by @ListImages@ in
-- paginated output. When this parameter is used, @ListImages@ only returns
-- @maxResults@ results in a single page along with a @nextToken@ response
-- element. The remaining results of the initial request can be seen by
-- sending another @ListImages@ request with the returned @nextToken@
-- value. This value can be between 1 and 1000. If this parameter is not
-- used, then @ListImages@ returns up to 100 results and a @nextToken@
-- value, if applicable.
listImages_maxResults :: Lens.Lens' ListImages (Prelude.Maybe Prelude.Natural)
listImages_maxResults :: Lens' ListImages (Maybe Natural)
listImages_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImages' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListImages' :: ListImages -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListImages
s@ListImages' {} Maybe Natural
a -> ListImages
s {$sel:maxResults:ListImages' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListImages)

-- | The @nextToken@ value returned from a previous paginated @ListImages@
-- request 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 value is @null@ when
-- there are no more results to return.
--
-- This token should be treated as an opaque identifier that is only used
-- to retrieve the next items in a list and not for other programmatic
-- purposes.
listImages_nextToken :: Lens.Lens' ListImages (Prelude.Maybe Prelude.Text)
listImages_nextToken :: Lens' ListImages (Maybe Text)
listImages_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImages' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListImages' :: ListImages -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListImages
s@ListImages' {} Maybe Text
a -> ListImages
s {$sel:nextToken:ListImages' :: Maybe Text
nextToken = Maybe Text
a} :: ListImages)

-- | The Amazon Web Services account ID associated with the registry that
-- contains the repository in which to list images. If you do not specify a
-- registry, the default registry is assumed.
listImages_registryId :: Lens.Lens' ListImages (Prelude.Maybe Prelude.Text)
listImages_registryId :: Lens' ListImages (Maybe Text)
listImages_registryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImages' {Maybe Text
registryId :: Maybe Text
$sel:registryId:ListImages' :: ListImages -> Maybe Text
registryId} -> Maybe Text
registryId) (\s :: ListImages
s@ListImages' {} Maybe Text
a -> ListImages
s {$sel:registryId:ListImages' :: Maybe Text
registryId = Maybe Text
a} :: ListImages)

-- | The repository with image IDs to be listed.
listImages_repositoryName :: Lens.Lens' ListImages Prelude.Text
listImages_repositoryName :: Lens' ListImages Text
listImages_repositoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImages' {Text
repositoryName :: Text
$sel:repositoryName:ListImages' :: ListImages -> Text
repositoryName} -> Text
repositoryName) (\s :: ListImages
s@ListImages' {} Text
a -> ListImages
s {$sel:repositoryName:ListImages' :: Text
repositoryName = Text
a} :: ListImages)

instance Core.AWSPager ListImages where
  page :: ListImages -> AWSResponse ListImages -> Maybe ListImages
page ListImages
rq AWSResponse ListImages
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListImages
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListImagesResponse (Maybe Text)
listImagesResponse_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 ListImages
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListImagesResponse (Maybe [ImageIdentifier])
listImagesResponse_imageIds
            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.$ ListImages
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListImages (Maybe Text)
listImages_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListImages
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListImagesResponse (Maybe Text)
listImagesResponse_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 ListImages where
  type AWSResponse ListImages = ListImagesResponse
  request :: (Service -> Service) -> ListImages -> Request ListImages
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 ListImages
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListImages)))
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 [ImageIdentifier] -> Maybe Text -> Int -> ListImagesResponse
ListImagesResponse'
            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
"imageIds" 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 ListImages where
  hashWithSalt :: Int -> ListImages -> Int
hashWithSalt Int
_salt ListImages' {Maybe Natural
Maybe Text
Maybe ListImagesFilter
Text
repositoryName :: Text
registryId :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filter' :: Maybe ListImagesFilter
$sel:repositoryName:ListImages' :: ListImages -> Text
$sel:registryId:ListImages' :: ListImages -> Maybe Text
$sel:nextToken:ListImages' :: ListImages -> Maybe Text
$sel:maxResults:ListImages' :: ListImages -> Maybe Natural
$sel:filter':ListImages' :: ListImages -> Maybe ListImagesFilter
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ListImagesFilter
filter'
      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 Text
registryId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
repositoryName

instance Prelude.NFData ListImages where
  rnf :: ListImages -> ()
rnf ListImages' {Maybe Natural
Maybe Text
Maybe ListImagesFilter
Text
repositoryName :: Text
registryId :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filter' :: Maybe ListImagesFilter
$sel:repositoryName:ListImages' :: ListImages -> Text
$sel:registryId:ListImages' :: ListImages -> Maybe Text
$sel:nextToken:ListImages' :: ListImages -> Maybe Text
$sel:maxResults:ListImages' :: ListImages -> Maybe Natural
$sel:filter':ListImages' :: ListImages -> Maybe ListImagesFilter
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ListImagesFilter
filter'
      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 Text
registryId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
repositoryName

instance Data.ToHeaders ListImages where
  toHeaders :: ListImages -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AmazonEC2ContainerRegistry_V20150921.ListImages" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

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

-- | /See:/ 'newListImagesResponse' smart constructor.
data ListImagesResponse = ListImagesResponse'
  { -- | The list of image IDs for the requested repository.
    ListImagesResponse -> Maybe [ImageIdentifier]
imageIds :: Prelude.Maybe [ImageIdentifier],
    -- | The @nextToken@ value to include in a future @ListImages@ request. When
    -- the results of a @ListImages@ request exceed @maxResults@, this value
    -- can be used to retrieve the next page of results. This value is @null@
    -- when there are no more results to return.
    ListImagesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListImagesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListImagesResponse -> ListImagesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListImagesResponse -> ListImagesResponse -> Bool
$c/= :: ListImagesResponse -> ListImagesResponse -> Bool
== :: ListImagesResponse -> ListImagesResponse -> Bool
$c== :: ListImagesResponse -> ListImagesResponse -> Bool
Prelude.Eq, ReadPrec [ListImagesResponse]
ReadPrec ListImagesResponse
Int -> ReadS ListImagesResponse
ReadS [ListImagesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListImagesResponse]
$creadListPrec :: ReadPrec [ListImagesResponse]
readPrec :: ReadPrec ListImagesResponse
$creadPrec :: ReadPrec ListImagesResponse
readList :: ReadS [ListImagesResponse]
$creadList :: ReadS [ListImagesResponse]
readsPrec :: Int -> ReadS ListImagesResponse
$creadsPrec :: Int -> ReadS ListImagesResponse
Prelude.Read, Int -> ListImagesResponse -> ShowS
[ListImagesResponse] -> ShowS
ListImagesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListImagesResponse] -> ShowS
$cshowList :: [ListImagesResponse] -> ShowS
show :: ListImagesResponse -> String
$cshow :: ListImagesResponse -> String
showsPrec :: Int -> ListImagesResponse -> ShowS
$cshowsPrec :: Int -> ListImagesResponse -> ShowS
Prelude.Show, forall x. Rep ListImagesResponse x -> ListImagesResponse
forall x. ListImagesResponse -> Rep ListImagesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListImagesResponse x -> ListImagesResponse
$cfrom :: forall x. ListImagesResponse -> Rep ListImagesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListImagesResponse' 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:
--
-- 'imageIds', 'listImagesResponse_imageIds' - The list of image IDs for the requested repository.
--
-- 'nextToken', 'listImagesResponse_nextToken' - The @nextToken@ value to include in a future @ListImages@ request. When
-- the results of a @ListImages@ request exceed @maxResults@, this value
-- can be used to retrieve the next page of results. This value is @null@
-- when there are no more results to return.
--
-- 'httpStatus', 'listImagesResponse_httpStatus' - The response's http status code.
newListImagesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListImagesResponse
newListImagesResponse :: Int -> ListImagesResponse
newListImagesResponse Int
pHttpStatus_ =
  ListImagesResponse'
    { $sel:imageIds:ListImagesResponse' :: Maybe [ImageIdentifier]
imageIds = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListImagesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListImagesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of image IDs for the requested repository.
listImagesResponse_imageIds :: Lens.Lens' ListImagesResponse (Prelude.Maybe [ImageIdentifier])
listImagesResponse_imageIds :: Lens' ListImagesResponse (Maybe [ImageIdentifier])
listImagesResponse_imageIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImagesResponse' {Maybe [ImageIdentifier]
imageIds :: Maybe [ImageIdentifier]
$sel:imageIds:ListImagesResponse' :: ListImagesResponse -> Maybe [ImageIdentifier]
imageIds} -> Maybe [ImageIdentifier]
imageIds) (\s :: ListImagesResponse
s@ListImagesResponse' {} Maybe [ImageIdentifier]
a -> ListImagesResponse
s {$sel:imageIds:ListImagesResponse' :: Maybe [ImageIdentifier]
imageIds = Maybe [ImageIdentifier]
a} :: ListImagesResponse) 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 to include in a future @ListImages@ request. When
-- the results of a @ListImages@ request exceed @maxResults@, this value
-- can be used to retrieve the next page of results. This value is @null@
-- when there are no more results to return.
listImagesResponse_nextToken :: Lens.Lens' ListImagesResponse (Prelude.Maybe Prelude.Text)
listImagesResponse_nextToken :: Lens' ListImagesResponse (Maybe Text)
listImagesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImagesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListImagesResponse' :: ListImagesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListImagesResponse
s@ListImagesResponse' {} Maybe Text
a -> ListImagesResponse
s {$sel:nextToken:ListImagesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListImagesResponse)

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

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