{-# 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.BatchCheckLayerAvailability
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Checks the availability of one or more image layers in a repository.
--
-- When an image is pushed to a repository, each image layer is checked to
-- verify if it has been uploaded before. If it has been uploaded, then the
-- image layer is skipped.
--
-- This operation is used by the Amazon ECR proxy and is not generally used
-- by customers for pulling and pushing images. In most cases, you should
-- use the @docker@ CLI to pull, tag, and push images.
module Amazonka.ECR.BatchCheckLayerAvailability
  ( -- * Creating a Request
    BatchCheckLayerAvailability (..),
    newBatchCheckLayerAvailability,

    -- * Request Lenses
    batchCheckLayerAvailability_registryId,
    batchCheckLayerAvailability_repositoryName,
    batchCheckLayerAvailability_layerDigests,

    -- * Destructuring the Response
    BatchCheckLayerAvailabilityResponse (..),
    newBatchCheckLayerAvailabilityResponse,

    -- * Response Lenses
    batchCheckLayerAvailabilityResponse_failures,
    batchCheckLayerAvailabilityResponse_layers,
    batchCheckLayerAvailabilityResponse_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:/ 'newBatchCheckLayerAvailability' smart constructor.
data BatchCheckLayerAvailability = BatchCheckLayerAvailability'
  { -- | The Amazon Web Services account ID associated with the registry that
    -- contains the image layers to check. If you do not specify a registry,
    -- the default registry is assumed.
    BatchCheckLayerAvailability -> Maybe Text
registryId :: Prelude.Maybe Prelude.Text,
    -- | The name of the repository that is associated with the image layers to
    -- check.
    BatchCheckLayerAvailability -> Text
repositoryName :: Prelude.Text,
    -- | The digests of the image layers to check.
    BatchCheckLayerAvailability -> NonEmpty Text
layerDigests :: Prelude.NonEmpty Prelude.Text
  }
  deriving (BatchCheckLayerAvailability -> BatchCheckLayerAvailability -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchCheckLayerAvailability -> BatchCheckLayerAvailability -> Bool
$c/= :: BatchCheckLayerAvailability -> BatchCheckLayerAvailability -> Bool
== :: BatchCheckLayerAvailability -> BatchCheckLayerAvailability -> Bool
$c== :: BatchCheckLayerAvailability -> BatchCheckLayerAvailability -> Bool
Prelude.Eq, ReadPrec [BatchCheckLayerAvailability]
ReadPrec BatchCheckLayerAvailability
Int -> ReadS BatchCheckLayerAvailability
ReadS [BatchCheckLayerAvailability]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchCheckLayerAvailability]
$creadListPrec :: ReadPrec [BatchCheckLayerAvailability]
readPrec :: ReadPrec BatchCheckLayerAvailability
$creadPrec :: ReadPrec BatchCheckLayerAvailability
readList :: ReadS [BatchCheckLayerAvailability]
$creadList :: ReadS [BatchCheckLayerAvailability]
readsPrec :: Int -> ReadS BatchCheckLayerAvailability
$creadsPrec :: Int -> ReadS BatchCheckLayerAvailability
Prelude.Read, Int -> BatchCheckLayerAvailability -> ShowS
[BatchCheckLayerAvailability] -> ShowS
BatchCheckLayerAvailability -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchCheckLayerAvailability] -> ShowS
$cshowList :: [BatchCheckLayerAvailability] -> ShowS
show :: BatchCheckLayerAvailability -> String
$cshow :: BatchCheckLayerAvailability -> String
showsPrec :: Int -> BatchCheckLayerAvailability -> ShowS
$cshowsPrec :: Int -> BatchCheckLayerAvailability -> ShowS
Prelude.Show, forall x.
Rep BatchCheckLayerAvailability x -> BatchCheckLayerAvailability
forall x.
BatchCheckLayerAvailability -> Rep BatchCheckLayerAvailability x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchCheckLayerAvailability x -> BatchCheckLayerAvailability
$cfrom :: forall x.
BatchCheckLayerAvailability -> Rep BatchCheckLayerAvailability x
Prelude.Generic)

-- |
-- Create a value of 'BatchCheckLayerAvailability' 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:
--
-- 'registryId', 'batchCheckLayerAvailability_registryId' - The Amazon Web Services account ID associated with the registry that
-- contains the image layers to check. If you do not specify a registry,
-- the default registry is assumed.
--
-- 'repositoryName', 'batchCheckLayerAvailability_repositoryName' - The name of the repository that is associated with the image layers to
-- check.
--
-- 'layerDigests', 'batchCheckLayerAvailability_layerDigests' - The digests of the image layers to check.
newBatchCheckLayerAvailability ::
  -- | 'repositoryName'
  Prelude.Text ->
  -- | 'layerDigests'
  Prelude.NonEmpty Prelude.Text ->
  BatchCheckLayerAvailability
newBatchCheckLayerAvailability :: Text -> NonEmpty Text -> BatchCheckLayerAvailability
newBatchCheckLayerAvailability
  Text
pRepositoryName_
  NonEmpty Text
pLayerDigests_ =
    BatchCheckLayerAvailability'
      { $sel:registryId:BatchCheckLayerAvailability' :: Maybe Text
registryId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:repositoryName:BatchCheckLayerAvailability' :: Text
repositoryName = Text
pRepositoryName_,
        $sel:layerDigests:BatchCheckLayerAvailability' :: NonEmpty Text
layerDigests =
          forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pLayerDigests_
      }

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

-- | The name of the repository that is associated with the image layers to
-- check.
batchCheckLayerAvailability_repositoryName :: Lens.Lens' BatchCheckLayerAvailability Prelude.Text
batchCheckLayerAvailability_repositoryName :: Lens' BatchCheckLayerAvailability Text
batchCheckLayerAvailability_repositoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchCheckLayerAvailability' {Text
repositoryName :: Text
$sel:repositoryName:BatchCheckLayerAvailability' :: BatchCheckLayerAvailability -> Text
repositoryName} -> Text
repositoryName) (\s :: BatchCheckLayerAvailability
s@BatchCheckLayerAvailability' {} Text
a -> BatchCheckLayerAvailability
s {$sel:repositoryName:BatchCheckLayerAvailability' :: Text
repositoryName = Text
a} :: BatchCheckLayerAvailability)

-- | The digests of the image layers to check.
batchCheckLayerAvailability_layerDigests :: Lens.Lens' BatchCheckLayerAvailability (Prelude.NonEmpty Prelude.Text)
batchCheckLayerAvailability_layerDigests :: Lens' BatchCheckLayerAvailability (NonEmpty Text)
batchCheckLayerAvailability_layerDigests = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchCheckLayerAvailability' {NonEmpty Text
layerDigests :: NonEmpty Text
$sel:layerDigests:BatchCheckLayerAvailability' :: BatchCheckLayerAvailability -> NonEmpty Text
layerDigests} -> NonEmpty Text
layerDigests) (\s :: BatchCheckLayerAvailability
s@BatchCheckLayerAvailability' {} NonEmpty Text
a -> BatchCheckLayerAvailability
s {$sel:layerDigests:BatchCheckLayerAvailability' :: NonEmpty Text
layerDigests = NonEmpty Text
a} :: BatchCheckLayerAvailability) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest BatchCheckLayerAvailability where
  type
    AWSResponse BatchCheckLayerAvailability =
      BatchCheckLayerAvailabilityResponse
  request :: (Service -> Service)
-> BatchCheckLayerAvailability
-> Request BatchCheckLayerAvailability
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 BatchCheckLayerAvailability
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BatchCheckLayerAvailability)))
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 [LayerFailure]
-> Maybe [Layer] -> Int -> BatchCheckLayerAvailabilityResponse
BatchCheckLayerAvailabilityResponse'
            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
"failures" 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
"layers" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable BatchCheckLayerAvailability where
  hashWithSalt :: Int -> BatchCheckLayerAvailability -> Int
hashWithSalt Int
_salt BatchCheckLayerAvailability' {Maybe Text
NonEmpty Text
Text
layerDigests :: NonEmpty Text
repositoryName :: Text
registryId :: Maybe Text
$sel:layerDigests:BatchCheckLayerAvailability' :: BatchCheckLayerAvailability -> NonEmpty Text
$sel:repositoryName:BatchCheckLayerAvailability' :: BatchCheckLayerAvailability -> Text
$sel:registryId:BatchCheckLayerAvailability' :: BatchCheckLayerAvailability -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
registryId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
repositoryName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
layerDigests

instance Prelude.NFData BatchCheckLayerAvailability where
  rnf :: BatchCheckLayerAvailability -> ()
rnf BatchCheckLayerAvailability' {Maybe Text
NonEmpty Text
Text
layerDigests :: NonEmpty Text
repositoryName :: Text
registryId :: Maybe Text
$sel:layerDigests:BatchCheckLayerAvailability' :: BatchCheckLayerAvailability -> NonEmpty Text
$sel:repositoryName:BatchCheckLayerAvailability' :: BatchCheckLayerAvailability -> Text
$sel:registryId:BatchCheckLayerAvailability' :: BatchCheckLayerAvailability -> Maybe Text
..} =
    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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
layerDigests

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

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

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

-- | /See:/ 'newBatchCheckLayerAvailabilityResponse' smart constructor.
data BatchCheckLayerAvailabilityResponse = BatchCheckLayerAvailabilityResponse'
  { -- | Any failures associated with the call.
    BatchCheckLayerAvailabilityResponse -> Maybe [LayerFailure]
failures :: Prelude.Maybe [LayerFailure],
    -- | A list of image layer objects corresponding to the image layer
    -- references in the request.
    BatchCheckLayerAvailabilityResponse -> Maybe [Layer]
layers :: Prelude.Maybe [Layer],
    -- | The response's http status code.
    BatchCheckLayerAvailabilityResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchCheckLayerAvailabilityResponse
-> BatchCheckLayerAvailabilityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchCheckLayerAvailabilityResponse
-> BatchCheckLayerAvailabilityResponse -> Bool
$c/= :: BatchCheckLayerAvailabilityResponse
-> BatchCheckLayerAvailabilityResponse -> Bool
== :: BatchCheckLayerAvailabilityResponse
-> BatchCheckLayerAvailabilityResponse -> Bool
$c== :: BatchCheckLayerAvailabilityResponse
-> BatchCheckLayerAvailabilityResponse -> Bool
Prelude.Eq, ReadPrec [BatchCheckLayerAvailabilityResponse]
ReadPrec BatchCheckLayerAvailabilityResponse
Int -> ReadS BatchCheckLayerAvailabilityResponse
ReadS [BatchCheckLayerAvailabilityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchCheckLayerAvailabilityResponse]
$creadListPrec :: ReadPrec [BatchCheckLayerAvailabilityResponse]
readPrec :: ReadPrec BatchCheckLayerAvailabilityResponse
$creadPrec :: ReadPrec BatchCheckLayerAvailabilityResponse
readList :: ReadS [BatchCheckLayerAvailabilityResponse]
$creadList :: ReadS [BatchCheckLayerAvailabilityResponse]
readsPrec :: Int -> ReadS BatchCheckLayerAvailabilityResponse
$creadsPrec :: Int -> ReadS BatchCheckLayerAvailabilityResponse
Prelude.Read, Int -> BatchCheckLayerAvailabilityResponse -> ShowS
[BatchCheckLayerAvailabilityResponse] -> ShowS
BatchCheckLayerAvailabilityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchCheckLayerAvailabilityResponse] -> ShowS
$cshowList :: [BatchCheckLayerAvailabilityResponse] -> ShowS
show :: BatchCheckLayerAvailabilityResponse -> String
$cshow :: BatchCheckLayerAvailabilityResponse -> String
showsPrec :: Int -> BatchCheckLayerAvailabilityResponse -> ShowS
$cshowsPrec :: Int -> BatchCheckLayerAvailabilityResponse -> ShowS
Prelude.Show, forall x.
Rep BatchCheckLayerAvailabilityResponse x
-> BatchCheckLayerAvailabilityResponse
forall x.
BatchCheckLayerAvailabilityResponse
-> Rep BatchCheckLayerAvailabilityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchCheckLayerAvailabilityResponse x
-> BatchCheckLayerAvailabilityResponse
$cfrom :: forall x.
BatchCheckLayerAvailabilityResponse
-> Rep BatchCheckLayerAvailabilityResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchCheckLayerAvailabilityResponse' 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:
--
-- 'failures', 'batchCheckLayerAvailabilityResponse_failures' - Any failures associated with the call.
--
-- 'layers', 'batchCheckLayerAvailabilityResponse_layers' - A list of image layer objects corresponding to the image layer
-- references in the request.
--
-- 'httpStatus', 'batchCheckLayerAvailabilityResponse_httpStatus' - The response's http status code.
newBatchCheckLayerAvailabilityResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchCheckLayerAvailabilityResponse
newBatchCheckLayerAvailabilityResponse :: Int -> BatchCheckLayerAvailabilityResponse
newBatchCheckLayerAvailabilityResponse Int
pHttpStatus_ =
  BatchCheckLayerAvailabilityResponse'
    { $sel:failures:BatchCheckLayerAvailabilityResponse' :: Maybe [LayerFailure]
failures =
        forall a. Maybe a
Prelude.Nothing,
      $sel:layers:BatchCheckLayerAvailabilityResponse' :: Maybe [Layer]
layers = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BatchCheckLayerAvailabilityResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Any failures associated with the call.
batchCheckLayerAvailabilityResponse_failures :: Lens.Lens' BatchCheckLayerAvailabilityResponse (Prelude.Maybe [LayerFailure])
batchCheckLayerAvailabilityResponse_failures :: Lens' BatchCheckLayerAvailabilityResponse (Maybe [LayerFailure])
batchCheckLayerAvailabilityResponse_failures = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchCheckLayerAvailabilityResponse' {Maybe [LayerFailure]
failures :: Maybe [LayerFailure]
$sel:failures:BatchCheckLayerAvailabilityResponse' :: BatchCheckLayerAvailabilityResponse -> Maybe [LayerFailure]
failures} -> Maybe [LayerFailure]
failures) (\s :: BatchCheckLayerAvailabilityResponse
s@BatchCheckLayerAvailabilityResponse' {} Maybe [LayerFailure]
a -> BatchCheckLayerAvailabilityResponse
s {$sel:failures:BatchCheckLayerAvailabilityResponse' :: Maybe [LayerFailure]
failures = Maybe [LayerFailure]
a} :: BatchCheckLayerAvailabilityResponse) 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

-- | A list of image layer objects corresponding to the image layer
-- references in the request.
batchCheckLayerAvailabilityResponse_layers :: Lens.Lens' BatchCheckLayerAvailabilityResponse (Prelude.Maybe [Layer])
batchCheckLayerAvailabilityResponse_layers :: Lens' BatchCheckLayerAvailabilityResponse (Maybe [Layer])
batchCheckLayerAvailabilityResponse_layers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchCheckLayerAvailabilityResponse' {Maybe [Layer]
layers :: Maybe [Layer]
$sel:layers:BatchCheckLayerAvailabilityResponse' :: BatchCheckLayerAvailabilityResponse -> Maybe [Layer]
layers} -> Maybe [Layer]
layers) (\s :: BatchCheckLayerAvailabilityResponse
s@BatchCheckLayerAvailabilityResponse' {} Maybe [Layer]
a -> BatchCheckLayerAvailabilityResponse
s {$sel:layers:BatchCheckLayerAvailabilityResponse' :: Maybe [Layer]
layers = Maybe [Layer]
a} :: BatchCheckLayerAvailabilityResponse) 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 response's http status code.
batchCheckLayerAvailabilityResponse_httpStatus :: Lens.Lens' BatchCheckLayerAvailabilityResponse Prelude.Int
batchCheckLayerAvailabilityResponse_httpStatus :: Lens' BatchCheckLayerAvailabilityResponse Int
batchCheckLayerAvailabilityResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchCheckLayerAvailabilityResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchCheckLayerAvailabilityResponse' :: BatchCheckLayerAvailabilityResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchCheckLayerAvailabilityResponse
s@BatchCheckLayerAvailabilityResponse' {} Int
a -> BatchCheckLayerAvailabilityResponse
s {$sel:httpStatus:BatchCheckLayerAvailabilityResponse' :: Int
httpStatus = Int
a} :: BatchCheckLayerAvailabilityResponse)

instance
  Prelude.NFData
    BatchCheckLayerAvailabilityResponse
  where
  rnf :: BatchCheckLayerAvailabilityResponse -> ()
rnf BatchCheckLayerAvailabilityResponse' {Int
Maybe [Layer]
Maybe [LayerFailure]
httpStatus :: Int
layers :: Maybe [Layer]
failures :: Maybe [LayerFailure]
$sel:httpStatus:BatchCheckLayerAvailabilityResponse' :: BatchCheckLayerAvailabilityResponse -> Int
$sel:layers:BatchCheckLayerAvailabilityResponse' :: BatchCheckLayerAvailabilityResponse -> Maybe [Layer]
$sel:failures:BatchCheckLayerAvailabilityResponse' :: BatchCheckLayerAvailabilityResponse -> Maybe [LayerFailure]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [LayerFailure]
failures
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Layer]
layers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus