{-# 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.UploadLayerPart
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Uploads an image layer part to Amazon ECR.
--
-- When an image is pushed, each new image layer is uploaded in parts. The
-- maximum size of each image layer part can be 20971520 bytes (or about
-- 20MB). The UploadLayerPart API is called once per each new image layer
-- part.
--
-- 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.UploadLayerPart
  ( -- * Creating a Request
    UploadLayerPart (..),
    newUploadLayerPart,

    -- * Request Lenses
    uploadLayerPart_registryId,
    uploadLayerPart_repositoryName,
    uploadLayerPart_uploadId,
    uploadLayerPart_partFirstByte,
    uploadLayerPart_partLastByte,
    uploadLayerPart_layerPartBlob,

    -- * Destructuring the Response
    UploadLayerPartResponse (..),
    newUploadLayerPartResponse,

    -- * Response Lenses
    uploadLayerPartResponse_lastByteReceived,
    uploadLayerPartResponse_registryId,
    uploadLayerPartResponse_repositoryName,
    uploadLayerPartResponse_uploadId,
    uploadLayerPartResponse_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:/ 'newUploadLayerPart' smart constructor.
data UploadLayerPart = UploadLayerPart'
  { -- | The Amazon Web Services account ID associated with the registry to which
    -- you are uploading layer parts. If you do not specify a registry, the
    -- default registry is assumed.
    UploadLayerPart -> Maybe Text
registryId :: Prelude.Maybe Prelude.Text,
    -- | The name of the repository to which you are uploading layer parts.
    UploadLayerPart -> Text
repositoryName :: Prelude.Text,
    -- | The upload ID from a previous InitiateLayerUpload operation to associate
    -- with the layer part upload.
    UploadLayerPart -> Text
uploadId :: Prelude.Text,
    -- | The position of the first byte of the layer part witin the overall image
    -- layer.
    UploadLayerPart -> Natural
partFirstByte :: Prelude.Natural,
    -- | The position of the last byte of the layer part within the overall image
    -- layer.
    UploadLayerPart -> Natural
partLastByte :: Prelude.Natural,
    -- | The base64-encoded layer part payload.
    UploadLayerPart -> Base64
layerPartBlob :: Data.Base64
  }
  deriving (UploadLayerPart -> UploadLayerPart -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UploadLayerPart -> UploadLayerPart -> Bool
$c/= :: UploadLayerPart -> UploadLayerPart -> Bool
== :: UploadLayerPart -> UploadLayerPart -> Bool
$c== :: UploadLayerPart -> UploadLayerPart -> Bool
Prelude.Eq, ReadPrec [UploadLayerPart]
ReadPrec UploadLayerPart
Int -> ReadS UploadLayerPart
ReadS [UploadLayerPart]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UploadLayerPart]
$creadListPrec :: ReadPrec [UploadLayerPart]
readPrec :: ReadPrec UploadLayerPart
$creadPrec :: ReadPrec UploadLayerPart
readList :: ReadS [UploadLayerPart]
$creadList :: ReadS [UploadLayerPart]
readsPrec :: Int -> ReadS UploadLayerPart
$creadsPrec :: Int -> ReadS UploadLayerPart
Prelude.Read, Int -> UploadLayerPart -> ShowS
[UploadLayerPart] -> ShowS
UploadLayerPart -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadLayerPart] -> ShowS
$cshowList :: [UploadLayerPart] -> ShowS
show :: UploadLayerPart -> String
$cshow :: UploadLayerPart -> String
showsPrec :: Int -> UploadLayerPart -> ShowS
$cshowsPrec :: Int -> UploadLayerPart -> ShowS
Prelude.Show, forall x. Rep UploadLayerPart x -> UploadLayerPart
forall x. UploadLayerPart -> Rep UploadLayerPart x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UploadLayerPart x -> UploadLayerPart
$cfrom :: forall x. UploadLayerPart -> Rep UploadLayerPart x
Prelude.Generic)

-- |
-- Create a value of 'UploadLayerPart' 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', 'uploadLayerPart_registryId' - The Amazon Web Services account ID associated with the registry to which
-- you are uploading layer parts. If you do not specify a registry, the
-- default registry is assumed.
--
-- 'repositoryName', 'uploadLayerPart_repositoryName' - The name of the repository to which you are uploading layer parts.
--
-- 'uploadId', 'uploadLayerPart_uploadId' - The upload ID from a previous InitiateLayerUpload operation to associate
-- with the layer part upload.
--
-- 'partFirstByte', 'uploadLayerPart_partFirstByte' - The position of the first byte of the layer part witin the overall image
-- layer.
--
-- 'partLastByte', 'uploadLayerPart_partLastByte' - The position of the last byte of the layer part within the overall image
-- layer.
--
-- 'layerPartBlob', 'uploadLayerPart_layerPartBlob' - The base64-encoded layer part payload.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
newUploadLayerPart ::
  -- | 'repositoryName'
  Prelude.Text ->
  -- | 'uploadId'
  Prelude.Text ->
  -- | 'partFirstByte'
  Prelude.Natural ->
  -- | 'partLastByte'
  Prelude.Natural ->
  -- | 'layerPartBlob'
  Prelude.ByteString ->
  UploadLayerPart
newUploadLayerPart :: Text -> Text -> Natural -> Natural -> ByteString -> UploadLayerPart
newUploadLayerPart
  Text
pRepositoryName_
  Text
pUploadId_
  Natural
pPartFirstByte_
  Natural
pPartLastByte_
  ByteString
pLayerPartBlob_ =
    UploadLayerPart'
      { $sel:registryId:UploadLayerPart' :: Maybe Text
registryId = forall a. Maybe a
Prelude.Nothing,
        $sel:repositoryName:UploadLayerPart' :: Text
repositoryName = Text
pRepositoryName_,
        $sel:uploadId:UploadLayerPart' :: Text
uploadId = Text
pUploadId_,
        $sel:partFirstByte:UploadLayerPart' :: Natural
partFirstByte = Natural
pPartFirstByte_,
        $sel:partLastByte:UploadLayerPart' :: Natural
partLastByte = Natural
pPartLastByte_,
        $sel:layerPartBlob:UploadLayerPart' :: Base64
layerPartBlob = Iso' Base64 ByteString
Data._Base64 forall t b. AReview t b -> b -> t
Lens.# ByteString
pLayerPartBlob_
      }

-- | The Amazon Web Services account ID associated with the registry to which
-- you are uploading layer parts. If you do not specify a registry, the
-- default registry is assumed.
uploadLayerPart_registryId :: Lens.Lens' UploadLayerPart (Prelude.Maybe Prelude.Text)
uploadLayerPart_registryId :: Lens' UploadLayerPart (Maybe Text)
uploadLayerPart_registryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadLayerPart' {Maybe Text
registryId :: Maybe Text
$sel:registryId:UploadLayerPart' :: UploadLayerPart -> Maybe Text
registryId} -> Maybe Text
registryId) (\s :: UploadLayerPart
s@UploadLayerPart' {} Maybe Text
a -> UploadLayerPart
s {$sel:registryId:UploadLayerPart' :: Maybe Text
registryId = Maybe Text
a} :: UploadLayerPart)

-- | The name of the repository to which you are uploading layer parts.
uploadLayerPart_repositoryName :: Lens.Lens' UploadLayerPart Prelude.Text
uploadLayerPart_repositoryName :: Lens' UploadLayerPart Text
uploadLayerPart_repositoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadLayerPart' {Text
repositoryName :: Text
$sel:repositoryName:UploadLayerPart' :: UploadLayerPart -> Text
repositoryName} -> Text
repositoryName) (\s :: UploadLayerPart
s@UploadLayerPart' {} Text
a -> UploadLayerPart
s {$sel:repositoryName:UploadLayerPart' :: Text
repositoryName = Text
a} :: UploadLayerPart)

-- | The upload ID from a previous InitiateLayerUpload operation to associate
-- with the layer part upload.
uploadLayerPart_uploadId :: Lens.Lens' UploadLayerPart Prelude.Text
uploadLayerPart_uploadId :: Lens' UploadLayerPart Text
uploadLayerPart_uploadId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadLayerPart' {Text
uploadId :: Text
$sel:uploadId:UploadLayerPart' :: UploadLayerPart -> Text
uploadId} -> Text
uploadId) (\s :: UploadLayerPart
s@UploadLayerPart' {} Text
a -> UploadLayerPart
s {$sel:uploadId:UploadLayerPart' :: Text
uploadId = Text
a} :: UploadLayerPart)

-- | The position of the first byte of the layer part witin the overall image
-- layer.
uploadLayerPart_partFirstByte :: Lens.Lens' UploadLayerPart Prelude.Natural
uploadLayerPart_partFirstByte :: Lens' UploadLayerPart Natural
uploadLayerPart_partFirstByte = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadLayerPart' {Natural
partFirstByte :: Natural
$sel:partFirstByte:UploadLayerPart' :: UploadLayerPart -> Natural
partFirstByte} -> Natural
partFirstByte) (\s :: UploadLayerPart
s@UploadLayerPart' {} Natural
a -> UploadLayerPart
s {$sel:partFirstByte:UploadLayerPart' :: Natural
partFirstByte = Natural
a} :: UploadLayerPart)

-- | The position of the last byte of the layer part within the overall image
-- layer.
uploadLayerPart_partLastByte :: Lens.Lens' UploadLayerPart Prelude.Natural
uploadLayerPart_partLastByte :: Lens' UploadLayerPart Natural
uploadLayerPart_partLastByte = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadLayerPart' {Natural
partLastByte :: Natural
$sel:partLastByte:UploadLayerPart' :: UploadLayerPart -> Natural
partLastByte} -> Natural
partLastByte) (\s :: UploadLayerPart
s@UploadLayerPart' {} Natural
a -> UploadLayerPart
s {$sel:partLastByte:UploadLayerPart' :: Natural
partLastByte = Natural
a} :: UploadLayerPart)

-- | The base64-encoded layer part payload.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
uploadLayerPart_layerPartBlob :: Lens.Lens' UploadLayerPart Prelude.ByteString
uploadLayerPart_layerPartBlob :: Lens' UploadLayerPart ByteString
uploadLayerPart_layerPartBlob = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadLayerPart' {Base64
layerPartBlob :: Base64
$sel:layerPartBlob:UploadLayerPart' :: UploadLayerPart -> Base64
layerPartBlob} -> Base64
layerPartBlob) (\s :: UploadLayerPart
s@UploadLayerPart' {} Base64
a -> UploadLayerPart
s {$sel:layerPartBlob:UploadLayerPart' :: Base64
layerPartBlob = Base64
a} :: UploadLayerPart) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Iso' Base64 ByteString
Data._Base64

instance Core.AWSRequest UploadLayerPart where
  type
    AWSResponse UploadLayerPart =
      UploadLayerPartResponse
  request :: (Service -> Service) -> UploadLayerPart -> Request UploadLayerPart
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 UploadLayerPart
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UploadLayerPart)))
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 Natural
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> UploadLayerPartResponse
UploadLayerPartResponse'
            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
"lastByteReceived")
            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
"registryId")
            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
"repositoryName")
            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
"uploadId")
            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 UploadLayerPart where
  hashWithSalt :: Int -> UploadLayerPart -> Int
hashWithSalt Int
_salt UploadLayerPart' {Natural
Maybe Text
Text
Base64
layerPartBlob :: Base64
partLastByte :: Natural
partFirstByte :: Natural
uploadId :: Text
repositoryName :: Text
registryId :: Maybe Text
$sel:layerPartBlob:UploadLayerPart' :: UploadLayerPart -> Base64
$sel:partLastByte:UploadLayerPart' :: UploadLayerPart -> Natural
$sel:partFirstByte:UploadLayerPart' :: UploadLayerPart -> Natural
$sel:uploadId:UploadLayerPart' :: UploadLayerPart -> Text
$sel:repositoryName:UploadLayerPart' :: UploadLayerPart -> Text
$sel:registryId:UploadLayerPart' :: UploadLayerPart -> 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` Text
uploadId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
partFirstByte
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
partLastByte
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Base64
layerPartBlob

instance Prelude.NFData UploadLayerPart where
  rnf :: UploadLayerPart -> ()
rnf UploadLayerPart' {Natural
Maybe Text
Text
Base64
layerPartBlob :: Base64
partLastByte :: Natural
partFirstByte :: Natural
uploadId :: Text
repositoryName :: Text
registryId :: Maybe Text
$sel:layerPartBlob:UploadLayerPart' :: UploadLayerPart -> Base64
$sel:partLastByte:UploadLayerPart' :: UploadLayerPart -> Natural
$sel:partFirstByte:UploadLayerPart' :: UploadLayerPart -> Natural
$sel:uploadId:UploadLayerPart' :: UploadLayerPart -> Text
$sel:repositoryName:UploadLayerPart' :: UploadLayerPart -> Text
$sel:registryId:UploadLayerPart' :: UploadLayerPart -> 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 Text
uploadId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
partFirstByte
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
partLastByte
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Base64
layerPartBlob

instance Data.ToHeaders UploadLayerPart where
  toHeaders :: UploadLayerPart -> 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.UploadLayerPart" ::
                          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 UploadLayerPart where
  toJSON :: UploadLayerPart -> Value
toJSON UploadLayerPart' {Natural
Maybe Text
Text
Base64
layerPartBlob :: Base64
partLastByte :: Natural
partFirstByte :: Natural
uploadId :: Text
repositoryName :: Text
registryId :: Maybe Text
$sel:layerPartBlob:UploadLayerPart' :: UploadLayerPart -> Base64
$sel:partLastByte:UploadLayerPart' :: UploadLayerPart -> Natural
$sel:partFirstByte:UploadLayerPart' :: UploadLayerPart -> Natural
$sel:uploadId:UploadLayerPart' :: UploadLayerPart -> Text
$sel:repositoryName:UploadLayerPart' :: UploadLayerPart -> Text
$sel:registryId:UploadLayerPart' :: UploadLayerPart -> 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
"uploadId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
uploadId),
            forall a. a -> Maybe a
Prelude.Just (Key
"partFirstByte" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
partFirstByte),
            forall a. a -> Maybe a
Prelude.Just (Key
"partLastByte" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
partLastByte),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"layerPartBlob" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Base64
layerPartBlob)
          ]
      )

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

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

-- | /See:/ 'newUploadLayerPartResponse' smart constructor.
data UploadLayerPartResponse = UploadLayerPartResponse'
  { -- | The integer value of the last byte received in the request.
    UploadLayerPartResponse -> Maybe Natural
lastByteReceived :: Prelude.Maybe Prelude.Natural,
    -- | The registry ID associated with the request.
    UploadLayerPartResponse -> Maybe Text
registryId :: Prelude.Maybe Prelude.Text,
    -- | The repository name associated with the request.
    UploadLayerPartResponse -> Maybe Text
repositoryName :: Prelude.Maybe Prelude.Text,
    -- | The upload ID associated with the request.
    UploadLayerPartResponse -> Maybe Text
uploadId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UploadLayerPartResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UploadLayerPartResponse -> UploadLayerPartResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UploadLayerPartResponse -> UploadLayerPartResponse -> Bool
$c/= :: UploadLayerPartResponse -> UploadLayerPartResponse -> Bool
== :: UploadLayerPartResponse -> UploadLayerPartResponse -> Bool
$c== :: UploadLayerPartResponse -> UploadLayerPartResponse -> Bool
Prelude.Eq, ReadPrec [UploadLayerPartResponse]
ReadPrec UploadLayerPartResponse
Int -> ReadS UploadLayerPartResponse
ReadS [UploadLayerPartResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UploadLayerPartResponse]
$creadListPrec :: ReadPrec [UploadLayerPartResponse]
readPrec :: ReadPrec UploadLayerPartResponse
$creadPrec :: ReadPrec UploadLayerPartResponse
readList :: ReadS [UploadLayerPartResponse]
$creadList :: ReadS [UploadLayerPartResponse]
readsPrec :: Int -> ReadS UploadLayerPartResponse
$creadsPrec :: Int -> ReadS UploadLayerPartResponse
Prelude.Read, Int -> UploadLayerPartResponse -> ShowS
[UploadLayerPartResponse] -> ShowS
UploadLayerPartResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadLayerPartResponse] -> ShowS
$cshowList :: [UploadLayerPartResponse] -> ShowS
show :: UploadLayerPartResponse -> String
$cshow :: UploadLayerPartResponse -> String
showsPrec :: Int -> UploadLayerPartResponse -> ShowS
$cshowsPrec :: Int -> UploadLayerPartResponse -> ShowS
Prelude.Show, forall x. Rep UploadLayerPartResponse x -> UploadLayerPartResponse
forall x. UploadLayerPartResponse -> Rep UploadLayerPartResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UploadLayerPartResponse x -> UploadLayerPartResponse
$cfrom :: forall x. UploadLayerPartResponse -> Rep UploadLayerPartResponse x
Prelude.Generic)

-- |
-- Create a value of 'UploadLayerPartResponse' 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:
--
-- 'lastByteReceived', 'uploadLayerPartResponse_lastByteReceived' - The integer value of the last byte received in the request.
--
-- 'registryId', 'uploadLayerPartResponse_registryId' - The registry ID associated with the request.
--
-- 'repositoryName', 'uploadLayerPartResponse_repositoryName' - The repository name associated with the request.
--
-- 'uploadId', 'uploadLayerPartResponse_uploadId' - The upload ID associated with the request.
--
-- 'httpStatus', 'uploadLayerPartResponse_httpStatus' - The response's http status code.
newUploadLayerPartResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UploadLayerPartResponse
newUploadLayerPartResponse :: Int -> UploadLayerPartResponse
newUploadLayerPartResponse Int
pHttpStatus_ =
  UploadLayerPartResponse'
    { $sel:lastByteReceived:UploadLayerPartResponse' :: Maybe Natural
lastByteReceived =
        forall a. Maybe a
Prelude.Nothing,
      $sel:registryId:UploadLayerPartResponse' :: Maybe Text
registryId = forall a. Maybe a
Prelude.Nothing,
      $sel:repositoryName:UploadLayerPartResponse' :: Maybe Text
repositoryName = forall a. Maybe a
Prelude.Nothing,
      $sel:uploadId:UploadLayerPartResponse' :: Maybe Text
uploadId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UploadLayerPartResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The integer value of the last byte received in the request.
uploadLayerPartResponse_lastByteReceived :: Lens.Lens' UploadLayerPartResponse (Prelude.Maybe Prelude.Natural)
uploadLayerPartResponse_lastByteReceived :: Lens' UploadLayerPartResponse (Maybe Natural)
uploadLayerPartResponse_lastByteReceived = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadLayerPartResponse' {Maybe Natural
lastByteReceived :: Maybe Natural
$sel:lastByteReceived:UploadLayerPartResponse' :: UploadLayerPartResponse -> Maybe Natural
lastByteReceived} -> Maybe Natural
lastByteReceived) (\s :: UploadLayerPartResponse
s@UploadLayerPartResponse' {} Maybe Natural
a -> UploadLayerPartResponse
s {$sel:lastByteReceived:UploadLayerPartResponse' :: Maybe Natural
lastByteReceived = Maybe Natural
a} :: UploadLayerPartResponse)

-- | The registry ID associated with the request.
uploadLayerPartResponse_registryId :: Lens.Lens' UploadLayerPartResponse (Prelude.Maybe Prelude.Text)
uploadLayerPartResponse_registryId :: Lens' UploadLayerPartResponse (Maybe Text)
uploadLayerPartResponse_registryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadLayerPartResponse' {Maybe Text
registryId :: Maybe Text
$sel:registryId:UploadLayerPartResponse' :: UploadLayerPartResponse -> Maybe Text
registryId} -> Maybe Text
registryId) (\s :: UploadLayerPartResponse
s@UploadLayerPartResponse' {} Maybe Text
a -> UploadLayerPartResponse
s {$sel:registryId:UploadLayerPartResponse' :: Maybe Text
registryId = Maybe Text
a} :: UploadLayerPartResponse)

-- | The repository name associated with the request.
uploadLayerPartResponse_repositoryName :: Lens.Lens' UploadLayerPartResponse (Prelude.Maybe Prelude.Text)
uploadLayerPartResponse_repositoryName :: Lens' UploadLayerPartResponse (Maybe Text)
uploadLayerPartResponse_repositoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadLayerPartResponse' {Maybe Text
repositoryName :: Maybe Text
$sel:repositoryName:UploadLayerPartResponse' :: UploadLayerPartResponse -> Maybe Text
repositoryName} -> Maybe Text
repositoryName) (\s :: UploadLayerPartResponse
s@UploadLayerPartResponse' {} Maybe Text
a -> UploadLayerPartResponse
s {$sel:repositoryName:UploadLayerPartResponse' :: Maybe Text
repositoryName = Maybe Text
a} :: UploadLayerPartResponse)

-- | The upload ID associated with the request.
uploadLayerPartResponse_uploadId :: Lens.Lens' UploadLayerPartResponse (Prelude.Maybe Prelude.Text)
uploadLayerPartResponse_uploadId :: Lens' UploadLayerPartResponse (Maybe Text)
uploadLayerPartResponse_uploadId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadLayerPartResponse' {Maybe Text
uploadId :: Maybe Text
$sel:uploadId:UploadLayerPartResponse' :: UploadLayerPartResponse -> Maybe Text
uploadId} -> Maybe Text
uploadId) (\s :: UploadLayerPartResponse
s@UploadLayerPartResponse' {} Maybe Text
a -> UploadLayerPartResponse
s {$sel:uploadId:UploadLayerPartResponse' :: Maybe Text
uploadId = Maybe Text
a} :: UploadLayerPartResponse)

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

instance Prelude.NFData UploadLayerPartResponse where
  rnf :: UploadLayerPartResponse -> ()
rnf UploadLayerPartResponse' {Int
Maybe Natural
Maybe Text
httpStatus :: Int
uploadId :: Maybe Text
repositoryName :: Maybe Text
registryId :: Maybe Text
lastByteReceived :: Maybe Natural
$sel:httpStatus:UploadLayerPartResponse' :: UploadLayerPartResponse -> Int
$sel:uploadId:UploadLayerPartResponse' :: UploadLayerPartResponse -> Maybe Text
$sel:repositoryName:UploadLayerPartResponse' :: UploadLayerPartResponse -> Maybe Text
$sel:registryId:UploadLayerPartResponse' :: UploadLayerPartResponse -> Maybe Text
$sel:lastByteReceived:UploadLayerPartResponse' :: UploadLayerPartResponse -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
lastByteReceived
      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 Maybe Text
repositoryName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
uploadId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus