{-# 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.DescribeImages
-- 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 metadata about the images in a repository.
--
-- Beginning with Docker version 1.9, the Docker client compresses image
-- layers before pushing them to a V2 Docker registry. The output of the
-- @docker images@ command shows the uncompressed image size, so it may
-- return a larger image size than the image sizes returned by
-- DescribeImages.
--
-- This operation returns paginated results.
module Amazonka.ECR.DescribeImages
  ( -- * Creating a Request
    DescribeImages (..),
    newDescribeImages,

    -- * Request Lenses
    describeImages_filter,
    describeImages_imageIds,
    describeImages_maxResults,
    describeImages_nextToken,
    describeImages_registryId,
    describeImages_repositoryName,

    -- * Destructuring the Response
    DescribeImagesResponse (..),
    newDescribeImagesResponse,

    -- * Response Lenses
    describeImagesResponse_imageDetails,
    describeImagesResponse_nextToken,
    describeImagesResponse_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:/ 'newDescribeImages' smart constructor.
data DescribeImages = DescribeImages'
  { -- | The filter key and value with which to filter your @DescribeImages@
    -- results.
    DescribeImages -> Maybe DescribeImagesFilter
filter' :: Prelude.Maybe DescribeImagesFilter,
    -- | The list of image IDs for the requested repository.
    DescribeImages -> Maybe [ImageIdentifier]
imageIds :: Prelude.Maybe [ImageIdentifier],
    -- | The maximum number of repository results returned by @DescribeImages@ in
    -- paginated output. When this parameter is used, @DescribeImages@ 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 @DescribeImages@ request with the returned
    -- @nextToken@ value. This value can be between 1 and 1000. If this
    -- parameter is not used, then @DescribeImages@ returns up to 100 results
    -- and a @nextToken@ value, if applicable. This option cannot be used when
    -- you specify images with @imageIds@.
    DescribeImages -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The @nextToken@ value returned from a previous paginated
    -- @DescribeImages@ 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 option cannot
    -- be used when you specify images with @imageIds@.
    DescribeImages -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account ID associated with the registry that
    -- contains the repository in which to describe images. If you do not
    -- specify a registry, the default registry is assumed.
    DescribeImages -> Maybe Text
registryId :: Prelude.Maybe Prelude.Text,
    -- | The repository that contains the images to describe.
    DescribeImages -> Text
repositoryName :: Prelude.Text
  }
  deriving (DescribeImages -> DescribeImages -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeImages -> DescribeImages -> Bool
$c/= :: DescribeImages -> DescribeImages -> Bool
== :: DescribeImages -> DescribeImages -> Bool
$c== :: DescribeImages -> DescribeImages -> Bool
Prelude.Eq, ReadPrec [DescribeImages]
ReadPrec DescribeImages
Int -> ReadS DescribeImages
ReadS [DescribeImages]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeImages]
$creadListPrec :: ReadPrec [DescribeImages]
readPrec :: ReadPrec DescribeImages
$creadPrec :: ReadPrec DescribeImages
readList :: ReadS [DescribeImages]
$creadList :: ReadS [DescribeImages]
readsPrec :: Int -> ReadS DescribeImages
$creadsPrec :: Int -> ReadS DescribeImages
Prelude.Read, Int -> DescribeImages -> ShowS
[DescribeImages] -> ShowS
DescribeImages -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeImages] -> ShowS
$cshowList :: [DescribeImages] -> ShowS
show :: DescribeImages -> String
$cshow :: DescribeImages -> String
showsPrec :: Int -> DescribeImages -> ShowS
$cshowsPrec :: Int -> DescribeImages -> ShowS
Prelude.Show, forall x. Rep DescribeImages x -> DescribeImages
forall x. DescribeImages -> Rep DescribeImages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeImages x -> DescribeImages
$cfrom :: forall x. DescribeImages -> Rep DescribeImages x
Prelude.Generic)

-- |
-- Create a value of 'DescribeImages' 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'', 'describeImages_filter' - The filter key and value with which to filter your @DescribeImages@
-- results.
--
-- 'imageIds', 'describeImages_imageIds' - The list of image IDs for the requested repository.
--
-- 'maxResults', 'describeImages_maxResults' - The maximum number of repository results returned by @DescribeImages@ in
-- paginated output. When this parameter is used, @DescribeImages@ 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 @DescribeImages@ request with the returned
-- @nextToken@ value. This value can be between 1 and 1000. If this
-- parameter is not used, then @DescribeImages@ returns up to 100 results
-- and a @nextToken@ value, if applicable. This option cannot be used when
-- you specify images with @imageIds@.
--
-- 'nextToken', 'describeImages_nextToken' - The @nextToken@ value returned from a previous paginated
-- @DescribeImages@ 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 option cannot
-- be used when you specify images with @imageIds@.
--
-- 'registryId', 'describeImages_registryId' - The Amazon Web Services account ID associated with the registry that
-- contains the repository in which to describe images. If you do not
-- specify a registry, the default registry is assumed.
--
-- 'repositoryName', 'describeImages_repositoryName' - The repository that contains the images to describe.
newDescribeImages ::
  -- | 'repositoryName'
  Prelude.Text ->
  DescribeImages
newDescribeImages :: Text -> DescribeImages
newDescribeImages Text
pRepositoryName_ =
  DescribeImages'
    { $sel:filter':DescribeImages' :: Maybe DescribeImagesFilter
filter' = forall a. Maybe a
Prelude.Nothing,
      $sel:imageIds:DescribeImages' :: Maybe [ImageIdentifier]
imageIds = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:DescribeImages' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeImages' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:registryId:DescribeImages' :: Maybe Text
registryId = forall a. Maybe a
Prelude.Nothing,
      $sel:repositoryName:DescribeImages' :: Text
repositoryName = Text
pRepositoryName_
    }

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

-- | The list of image IDs for the requested repository.
describeImages_imageIds :: Lens.Lens' DescribeImages (Prelude.Maybe [ImageIdentifier])
describeImages_imageIds :: Lens' DescribeImages (Maybe [ImageIdentifier])
describeImages_imageIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeImages' {Maybe [ImageIdentifier]
imageIds :: Maybe [ImageIdentifier]
$sel:imageIds:DescribeImages' :: DescribeImages -> Maybe [ImageIdentifier]
imageIds} -> Maybe [ImageIdentifier]
imageIds) (\s :: DescribeImages
s@DescribeImages' {} Maybe [ImageIdentifier]
a -> DescribeImages
s {$sel:imageIds:DescribeImages' :: Maybe [ImageIdentifier]
imageIds = Maybe [ImageIdentifier]
a} :: DescribeImages) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The maximum number of repository results returned by @DescribeImages@ in
-- paginated output. When this parameter is used, @DescribeImages@ 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 @DescribeImages@ request with the returned
-- @nextToken@ value. This value can be between 1 and 1000. If this
-- parameter is not used, then @DescribeImages@ returns up to 100 results
-- and a @nextToken@ value, if applicable. This option cannot be used when
-- you specify images with @imageIds@.
describeImages_maxResults :: Lens.Lens' DescribeImages (Prelude.Maybe Prelude.Natural)
describeImages_maxResults :: Lens' DescribeImages (Maybe Natural)
describeImages_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeImages' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:DescribeImages' :: DescribeImages -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: DescribeImages
s@DescribeImages' {} Maybe Natural
a -> DescribeImages
s {$sel:maxResults:DescribeImages' :: Maybe Natural
maxResults = Maybe Natural
a} :: DescribeImages)

-- | The @nextToken@ value returned from a previous paginated
-- @DescribeImages@ 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 option cannot
-- be used when you specify images with @imageIds@.
describeImages_nextToken :: Lens.Lens' DescribeImages (Prelude.Maybe Prelude.Text)
describeImages_nextToken :: Lens' DescribeImages (Maybe Text)
describeImages_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeImages' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeImages' :: DescribeImages -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeImages
s@DescribeImages' {} Maybe Text
a -> DescribeImages
s {$sel:nextToken:DescribeImages' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeImages)

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

-- | The repository that contains the images to describe.
describeImages_repositoryName :: Lens.Lens' DescribeImages Prelude.Text
describeImages_repositoryName :: Lens' DescribeImages Text
describeImages_repositoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeImages' {Text
repositoryName :: Text
$sel:repositoryName:DescribeImages' :: DescribeImages -> Text
repositoryName} -> Text
repositoryName) (\s :: DescribeImages
s@DescribeImages' {} Text
a -> DescribeImages
s {$sel:repositoryName:DescribeImages' :: Text
repositoryName = Text
a} :: DescribeImages)

instance Core.AWSPager DescribeImages where
  page :: DescribeImages
-> AWSResponse DescribeImages -> Maybe DescribeImages
page DescribeImages
rq AWSResponse DescribeImages
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeImages
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeImagesResponse (Maybe Text)
describeImagesResponse_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 DescribeImages
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeImagesResponse (Maybe [ImageDetail])
describeImagesResponse_imageDetails
            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.$ DescribeImages
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeImages (Maybe Text)
describeImages_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeImages
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeImagesResponse (Maybe Text)
describeImagesResponse_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 DescribeImages where
  type
    AWSResponse DescribeImages =
      DescribeImagesResponse
  request :: (Service -> Service) -> DescribeImages -> Request DescribeImages
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 DescribeImages
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeImages)))
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 [ImageDetail] -> Maybe Text -> Int -> DescribeImagesResponse
DescribeImagesResponse'
            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
"imageDetails" 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 DescribeImages where
  hashWithSalt :: Int -> DescribeImages -> Int
hashWithSalt Int
_salt DescribeImages' {Maybe Natural
Maybe [ImageIdentifier]
Maybe Text
Maybe DescribeImagesFilter
Text
repositoryName :: Text
registryId :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
imageIds :: Maybe [ImageIdentifier]
filter' :: Maybe DescribeImagesFilter
$sel:repositoryName:DescribeImages' :: DescribeImages -> Text
$sel:registryId:DescribeImages' :: DescribeImages -> Maybe Text
$sel:nextToken:DescribeImages' :: DescribeImages -> Maybe Text
$sel:maxResults:DescribeImages' :: DescribeImages -> Maybe Natural
$sel:imageIds:DescribeImages' :: DescribeImages -> Maybe [ImageIdentifier]
$sel:filter':DescribeImages' :: DescribeImages -> Maybe DescribeImagesFilter
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DescribeImagesFilter
filter'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ImageIdentifier]
imageIds
      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 DescribeImages where
  rnf :: DescribeImages -> ()
rnf DescribeImages' {Maybe Natural
Maybe [ImageIdentifier]
Maybe Text
Maybe DescribeImagesFilter
Text
repositoryName :: Text
registryId :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
imageIds :: Maybe [ImageIdentifier]
filter' :: Maybe DescribeImagesFilter
$sel:repositoryName:DescribeImages' :: DescribeImages -> Text
$sel:registryId:DescribeImages' :: DescribeImages -> Maybe Text
$sel:nextToken:DescribeImages' :: DescribeImages -> Maybe Text
$sel:maxResults:DescribeImages' :: DescribeImages -> Maybe Natural
$sel:imageIds:DescribeImages' :: DescribeImages -> Maybe [ImageIdentifier]
$sel:filter':DescribeImages' :: DescribeImages -> Maybe DescribeImagesFilter
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DescribeImagesFilter
filter'
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 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 DescribeImages where
  toHeaders :: DescribeImages -> 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.DescribeImages" ::
                          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 DescribeImages where
  toJSON :: DescribeImages -> Value
toJSON DescribeImages' {Maybe Natural
Maybe [ImageIdentifier]
Maybe Text
Maybe DescribeImagesFilter
Text
repositoryName :: Text
registryId :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
imageIds :: Maybe [ImageIdentifier]
filter' :: Maybe DescribeImagesFilter
$sel:repositoryName:DescribeImages' :: DescribeImages -> Text
$sel:registryId:DescribeImages' :: DescribeImages -> Maybe Text
$sel:nextToken:DescribeImages' :: DescribeImages -> Maybe Text
$sel:maxResults:DescribeImages' :: DescribeImages -> Maybe Natural
$sel:imageIds:DescribeImages' :: DescribeImages -> Maybe [ImageIdentifier]
$sel:filter':DescribeImages' :: DescribeImages -> Maybe DescribeImagesFilter
..} =
    [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 DescribeImagesFilter
filter',
            (Key
"imageIds" 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 [ImageIdentifier]
imageIds,
            (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 DescribeImages where
  toPath :: DescribeImages -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDescribeImagesResponse' smart constructor.
data DescribeImagesResponse = DescribeImagesResponse'
  { -- | A list of ImageDetail objects that contain data about the image.
    DescribeImagesResponse -> Maybe [ImageDetail]
imageDetails :: Prelude.Maybe [ImageDetail],
    -- | The @nextToken@ value to include in a future @DescribeImages@ request.
    -- When the results of a @DescribeImages@ 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.
    DescribeImagesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeImagesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeImagesResponse -> DescribeImagesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeImagesResponse -> DescribeImagesResponse -> Bool
$c/= :: DescribeImagesResponse -> DescribeImagesResponse -> Bool
== :: DescribeImagesResponse -> DescribeImagesResponse -> Bool
$c== :: DescribeImagesResponse -> DescribeImagesResponse -> Bool
Prelude.Eq, ReadPrec [DescribeImagesResponse]
ReadPrec DescribeImagesResponse
Int -> ReadS DescribeImagesResponse
ReadS [DescribeImagesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeImagesResponse]
$creadListPrec :: ReadPrec [DescribeImagesResponse]
readPrec :: ReadPrec DescribeImagesResponse
$creadPrec :: ReadPrec DescribeImagesResponse
readList :: ReadS [DescribeImagesResponse]
$creadList :: ReadS [DescribeImagesResponse]
readsPrec :: Int -> ReadS DescribeImagesResponse
$creadsPrec :: Int -> ReadS DescribeImagesResponse
Prelude.Read, Int -> DescribeImagesResponse -> ShowS
[DescribeImagesResponse] -> ShowS
DescribeImagesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeImagesResponse] -> ShowS
$cshowList :: [DescribeImagesResponse] -> ShowS
show :: DescribeImagesResponse -> String
$cshow :: DescribeImagesResponse -> String
showsPrec :: Int -> DescribeImagesResponse -> ShowS
$cshowsPrec :: Int -> DescribeImagesResponse -> ShowS
Prelude.Show, forall x. Rep DescribeImagesResponse x -> DescribeImagesResponse
forall x. DescribeImagesResponse -> Rep DescribeImagesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeImagesResponse x -> DescribeImagesResponse
$cfrom :: forall x. DescribeImagesResponse -> Rep DescribeImagesResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeImagesResponse' 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:
--
-- 'imageDetails', 'describeImagesResponse_imageDetails' - A list of ImageDetail objects that contain data about the image.
--
-- 'nextToken', 'describeImagesResponse_nextToken' - The @nextToken@ value to include in a future @DescribeImages@ request.
-- When the results of a @DescribeImages@ 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', 'describeImagesResponse_httpStatus' - The response's http status code.
newDescribeImagesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeImagesResponse
newDescribeImagesResponse :: Int -> DescribeImagesResponse
newDescribeImagesResponse Int
pHttpStatus_ =
  DescribeImagesResponse'
    { $sel:imageDetails:DescribeImagesResponse' :: Maybe [ImageDetail]
imageDetails =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeImagesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeImagesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of ImageDetail objects that contain data about the image.
describeImagesResponse_imageDetails :: Lens.Lens' DescribeImagesResponse (Prelude.Maybe [ImageDetail])
describeImagesResponse_imageDetails :: Lens' DescribeImagesResponse (Maybe [ImageDetail])
describeImagesResponse_imageDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeImagesResponse' {Maybe [ImageDetail]
imageDetails :: Maybe [ImageDetail]
$sel:imageDetails:DescribeImagesResponse' :: DescribeImagesResponse -> Maybe [ImageDetail]
imageDetails} -> Maybe [ImageDetail]
imageDetails) (\s :: DescribeImagesResponse
s@DescribeImagesResponse' {} Maybe [ImageDetail]
a -> DescribeImagesResponse
s {$sel:imageDetails:DescribeImagesResponse' :: Maybe [ImageDetail]
imageDetails = Maybe [ImageDetail]
a} :: DescribeImagesResponse) 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 @DescribeImages@ request.
-- When the results of a @DescribeImages@ 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.
describeImagesResponse_nextToken :: Lens.Lens' DescribeImagesResponse (Prelude.Maybe Prelude.Text)
describeImagesResponse_nextToken :: Lens' DescribeImagesResponse (Maybe Text)
describeImagesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeImagesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeImagesResponse' :: DescribeImagesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeImagesResponse
s@DescribeImagesResponse' {} Maybe Text
a -> DescribeImagesResponse
s {$sel:nextToken:DescribeImagesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeImagesResponse)

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

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