{-# 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.DeletePullThroughCacheRule
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a pull through cache rule.
module Amazonka.ECR.DeletePullThroughCacheRule
  ( -- * Creating a Request
    DeletePullThroughCacheRule (..),
    newDeletePullThroughCacheRule,

    -- * Request Lenses
    deletePullThroughCacheRule_registryId,
    deletePullThroughCacheRule_ecrRepositoryPrefix,

    -- * Destructuring the Response
    DeletePullThroughCacheRuleResponse (..),
    newDeletePullThroughCacheRuleResponse,

    -- * Response Lenses
    deletePullThroughCacheRuleResponse_createdAt,
    deletePullThroughCacheRuleResponse_ecrRepositoryPrefix,
    deletePullThroughCacheRuleResponse_registryId,
    deletePullThroughCacheRuleResponse_upstreamRegistryUrl,
    deletePullThroughCacheRuleResponse_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:/ 'newDeletePullThroughCacheRule' smart constructor.
data DeletePullThroughCacheRule = DeletePullThroughCacheRule'
  { -- | The Amazon Web Services account ID associated with the registry that
    -- contains the pull through cache rule. If you do not specify a registry,
    -- the default registry is assumed.
    DeletePullThroughCacheRule -> Maybe Text
registryId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon ECR repository prefix associated with the pull through cache
    -- rule to delete.
    DeletePullThroughCacheRule -> Text
ecrRepositoryPrefix :: Prelude.Text
  }
  deriving (DeletePullThroughCacheRule -> DeletePullThroughCacheRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePullThroughCacheRule -> DeletePullThroughCacheRule -> Bool
$c/= :: DeletePullThroughCacheRule -> DeletePullThroughCacheRule -> Bool
== :: DeletePullThroughCacheRule -> DeletePullThroughCacheRule -> Bool
$c== :: DeletePullThroughCacheRule -> DeletePullThroughCacheRule -> Bool
Prelude.Eq, ReadPrec [DeletePullThroughCacheRule]
ReadPrec DeletePullThroughCacheRule
Int -> ReadS DeletePullThroughCacheRule
ReadS [DeletePullThroughCacheRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePullThroughCacheRule]
$creadListPrec :: ReadPrec [DeletePullThroughCacheRule]
readPrec :: ReadPrec DeletePullThroughCacheRule
$creadPrec :: ReadPrec DeletePullThroughCacheRule
readList :: ReadS [DeletePullThroughCacheRule]
$creadList :: ReadS [DeletePullThroughCacheRule]
readsPrec :: Int -> ReadS DeletePullThroughCacheRule
$creadsPrec :: Int -> ReadS DeletePullThroughCacheRule
Prelude.Read, Int -> DeletePullThroughCacheRule -> ShowS
[DeletePullThroughCacheRule] -> ShowS
DeletePullThroughCacheRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePullThroughCacheRule] -> ShowS
$cshowList :: [DeletePullThroughCacheRule] -> ShowS
show :: DeletePullThroughCacheRule -> String
$cshow :: DeletePullThroughCacheRule -> String
showsPrec :: Int -> DeletePullThroughCacheRule -> ShowS
$cshowsPrec :: Int -> DeletePullThroughCacheRule -> ShowS
Prelude.Show, forall x.
Rep DeletePullThroughCacheRule x -> DeletePullThroughCacheRule
forall x.
DeletePullThroughCacheRule -> Rep DeletePullThroughCacheRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeletePullThroughCacheRule x -> DeletePullThroughCacheRule
$cfrom :: forall x.
DeletePullThroughCacheRule -> Rep DeletePullThroughCacheRule x
Prelude.Generic)

-- |
-- Create a value of 'DeletePullThroughCacheRule' 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', 'deletePullThroughCacheRule_registryId' - The Amazon Web Services account ID associated with the registry that
-- contains the pull through cache rule. If you do not specify a registry,
-- the default registry is assumed.
--
-- 'ecrRepositoryPrefix', 'deletePullThroughCacheRule_ecrRepositoryPrefix' - The Amazon ECR repository prefix associated with the pull through cache
-- rule to delete.
newDeletePullThroughCacheRule ::
  -- | 'ecrRepositoryPrefix'
  Prelude.Text ->
  DeletePullThroughCacheRule
newDeletePullThroughCacheRule :: Text -> DeletePullThroughCacheRule
newDeletePullThroughCacheRule Text
pEcrRepositoryPrefix_ =
  DeletePullThroughCacheRule'
    { $sel:registryId:DeletePullThroughCacheRule' :: Maybe Text
registryId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ecrRepositoryPrefix:DeletePullThroughCacheRule' :: Text
ecrRepositoryPrefix = Text
pEcrRepositoryPrefix_
    }

-- | The Amazon Web Services account ID associated with the registry that
-- contains the pull through cache rule. If you do not specify a registry,
-- the default registry is assumed.
deletePullThroughCacheRule_registryId :: Lens.Lens' DeletePullThroughCacheRule (Prelude.Maybe Prelude.Text)
deletePullThroughCacheRule_registryId :: Lens' DeletePullThroughCacheRule (Maybe Text)
deletePullThroughCacheRule_registryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePullThroughCacheRule' {Maybe Text
registryId :: Maybe Text
$sel:registryId:DeletePullThroughCacheRule' :: DeletePullThroughCacheRule -> Maybe Text
registryId} -> Maybe Text
registryId) (\s :: DeletePullThroughCacheRule
s@DeletePullThroughCacheRule' {} Maybe Text
a -> DeletePullThroughCacheRule
s {$sel:registryId:DeletePullThroughCacheRule' :: Maybe Text
registryId = Maybe Text
a} :: DeletePullThroughCacheRule)

-- | The Amazon ECR repository prefix associated with the pull through cache
-- rule to delete.
deletePullThroughCacheRule_ecrRepositoryPrefix :: Lens.Lens' DeletePullThroughCacheRule Prelude.Text
deletePullThroughCacheRule_ecrRepositoryPrefix :: Lens' DeletePullThroughCacheRule Text
deletePullThroughCacheRule_ecrRepositoryPrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePullThroughCacheRule' {Text
ecrRepositoryPrefix :: Text
$sel:ecrRepositoryPrefix:DeletePullThroughCacheRule' :: DeletePullThroughCacheRule -> Text
ecrRepositoryPrefix} -> Text
ecrRepositoryPrefix) (\s :: DeletePullThroughCacheRule
s@DeletePullThroughCacheRule' {} Text
a -> DeletePullThroughCacheRule
s {$sel:ecrRepositoryPrefix:DeletePullThroughCacheRule' :: Text
ecrRepositoryPrefix = Text
a} :: DeletePullThroughCacheRule)

instance Core.AWSRequest DeletePullThroughCacheRule where
  type
    AWSResponse DeletePullThroughCacheRule =
      DeletePullThroughCacheRuleResponse
  request :: (Service -> Service)
-> DeletePullThroughCacheRule -> Request DeletePullThroughCacheRule
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 DeletePullThroughCacheRule
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeletePullThroughCacheRule)))
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 POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> DeletePullThroughCacheRuleResponse
DeletePullThroughCacheRuleResponse'
            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
"createdAt")
            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
"ecrRepositoryPrefix")
            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
"upstreamRegistryUrl")
            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 DeletePullThroughCacheRule where
  hashWithSalt :: Int -> DeletePullThroughCacheRule -> Int
hashWithSalt Int
_salt DeletePullThroughCacheRule' {Maybe Text
Text
ecrRepositoryPrefix :: Text
registryId :: Maybe Text
$sel:ecrRepositoryPrefix:DeletePullThroughCacheRule' :: DeletePullThroughCacheRule -> Text
$sel:registryId:DeletePullThroughCacheRule' :: DeletePullThroughCacheRule -> 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
ecrRepositoryPrefix

instance Prelude.NFData DeletePullThroughCacheRule where
  rnf :: DeletePullThroughCacheRule -> ()
rnf DeletePullThroughCacheRule' {Maybe Text
Text
ecrRepositoryPrefix :: Text
registryId :: Maybe Text
$sel:ecrRepositoryPrefix:DeletePullThroughCacheRule' :: DeletePullThroughCacheRule -> Text
$sel:registryId:DeletePullThroughCacheRule' :: DeletePullThroughCacheRule -> 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
ecrRepositoryPrefix

instance Data.ToHeaders DeletePullThroughCacheRule where
  toHeaders :: DeletePullThroughCacheRule -> 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.DeletePullThroughCacheRule" ::
                          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 DeletePullThroughCacheRule where
  toJSON :: DeletePullThroughCacheRule -> Value
toJSON DeletePullThroughCacheRule' {Maybe Text
Text
ecrRepositoryPrefix :: Text
registryId :: Maybe Text
$sel:ecrRepositoryPrefix:DeletePullThroughCacheRule' :: DeletePullThroughCacheRule -> Text
$sel:registryId:DeletePullThroughCacheRule' :: DeletePullThroughCacheRule -> 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
"ecrRepositoryPrefix" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
ecrRepositoryPrefix)
          ]
      )

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

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

-- | /See:/ 'newDeletePullThroughCacheRuleResponse' smart constructor.
data DeletePullThroughCacheRuleResponse = DeletePullThroughCacheRuleResponse'
  { -- | The timestamp associated with the pull through cache rule.
    DeletePullThroughCacheRuleResponse -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The Amazon ECR repository prefix associated with the request.
    DeletePullThroughCacheRuleResponse -> Maybe Text
ecrRepositoryPrefix :: Prelude.Maybe Prelude.Text,
    -- | The registry ID associated with the request.
    DeletePullThroughCacheRuleResponse -> Maybe Text
registryId :: Prelude.Maybe Prelude.Text,
    -- | The upstream registry URL associated with the pull through cache rule.
    DeletePullThroughCacheRuleResponse -> Maybe Text
upstreamRegistryUrl :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DeletePullThroughCacheRuleResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeletePullThroughCacheRuleResponse
-> DeletePullThroughCacheRuleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePullThroughCacheRuleResponse
-> DeletePullThroughCacheRuleResponse -> Bool
$c/= :: DeletePullThroughCacheRuleResponse
-> DeletePullThroughCacheRuleResponse -> Bool
== :: DeletePullThroughCacheRuleResponse
-> DeletePullThroughCacheRuleResponse -> Bool
$c== :: DeletePullThroughCacheRuleResponse
-> DeletePullThroughCacheRuleResponse -> Bool
Prelude.Eq, ReadPrec [DeletePullThroughCacheRuleResponse]
ReadPrec DeletePullThroughCacheRuleResponse
Int -> ReadS DeletePullThroughCacheRuleResponse
ReadS [DeletePullThroughCacheRuleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePullThroughCacheRuleResponse]
$creadListPrec :: ReadPrec [DeletePullThroughCacheRuleResponse]
readPrec :: ReadPrec DeletePullThroughCacheRuleResponse
$creadPrec :: ReadPrec DeletePullThroughCacheRuleResponse
readList :: ReadS [DeletePullThroughCacheRuleResponse]
$creadList :: ReadS [DeletePullThroughCacheRuleResponse]
readsPrec :: Int -> ReadS DeletePullThroughCacheRuleResponse
$creadsPrec :: Int -> ReadS DeletePullThroughCacheRuleResponse
Prelude.Read, Int -> DeletePullThroughCacheRuleResponse -> ShowS
[DeletePullThroughCacheRuleResponse] -> ShowS
DeletePullThroughCacheRuleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePullThroughCacheRuleResponse] -> ShowS
$cshowList :: [DeletePullThroughCacheRuleResponse] -> ShowS
show :: DeletePullThroughCacheRuleResponse -> String
$cshow :: DeletePullThroughCacheRuleResponse -> String
showsPrec :: Int -> DeletePullThroughCacheRuleResponse -> ShowS
$cshowsPrec :: Int -> DeletePullThroughCacheRuleResponse -> ShowS
Prelude.Show, forall x.
Rep DeletePullThroughCacheRuleResponse x
-> DeletePullThroughCacheRuleResponse
forall x.
DeletePullThroughCacheRuleResponse
-> Rep DeletePullThroughCacheRuleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeletePullThroughCacheRuleResponse x
-> DeletePullThroughCacheRuleResponse
$cfrom :: forall x.
DeletePullThroughCacheRuleResponse
-> Rep DeletePullThroughCacheRuleResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeletePullThroughCacheRuleResponse' 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:
--
-- 'createdAt', 'deletePullThroughCacheRuleResponse_createdAt' - The timestamp associated with the pull through cache rule.
--
-- 'ecrRepositoryPrefix', 'deletePullThroughCacheRuleResponse_ecrRepositoryPrefix' - The Amazon ECR repository prefix associated with the request.
--
-- 'registryId', 'deletePullThroughCacheRuleResponse_registryId' - The registry ID associated with the request.
--
-- 'upstreamRegistryUrl', 'deletePullThroughCacheRuleResponse_upstreamRegistryUrl' - The upstream registry URL associated with the pull through cache rule.
--
-- 'httpStatus', 'deletePullThroughCacheRuleResponse_httpStatus' - The response's http status code.
newDeletePullThroughCacheRuleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeletePullThroughCacheRuleResponse
newDeletePullThroughCacheRuleResponse :: Int -> DeletePullThroughCacheRuleResponse
newDeletePullThroughCacheRuleResponse Int
pHttpStatus_ =
  DeletePullThroughCacheRuleResponse'
    { $sel:createdAt:DeletePullThroughCacheRuleResponse' :: Maybe POSIX
createdAt =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ecrRepositoryPrefix:DeletePullThroughCacheRuleResponse' :: Maybe Text
ecrRepositoryPrefix = forall a. Maybe a
Prelude.Nothing,
      $sel:registryId:DeletePullThroughCacheRuleResponse' :: Maybe Text
registryId = forall a. Maybe a
Prelude.Nothing,
      $sel:upstreamRegistryUrl:DeletePullThroughCacheRuleResponse' :: Maybe Text
upstreamRegistryUrl = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeletePullThroughCacheRuleResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The timestamp associated with the pull through cache rule.
deletePullThroughCacheRuleResponse_createdAt :: Lens.Lens' DeletePullThroughCacheRuleResponse (Prelude.Maybe Prelude.UTCTime)
deletePullThroughCacheRuleResponse_createdAt :: Lens' DeletePullThroughCacheRuleResponse (Maybe UTCTime)
deletePullThroughCacheRuleResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePullThroughCacheRuleResponse' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:DeletePullThroughCacheRuleResponse' :: DeletePullThroughCacheRuleResponse -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: DeletePullThroughCacheRuleResponse
s@DeletePullThroughCacheRuleResponse' {} Maybe POSIX
a -> DeletePullThroughCacheRuleResponse
s {$sel:createdAt:DeletePullThroughCacheRuleResponse' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: DeletePullThroughCacheRuleResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The Amazon ECR repository prefix associated with the request.
deletePullThroughCacheRuleResponse_ecrRepositoryPrefix :: Lens.Lens' DeletePullThroughCacheRuleResponse (Prelude.Maybe Prelude.Text)
deletePullThroughCacheRuleResponse_ecrRepositoryPrefix :: Lens' DeletePullThroughCacheRuleResponse (Maybe Text)
deletePullThroughCacheRuleResponse_ecrRepositoryPrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePullThroughCacheRuleResponse' {Maybe Text
ecrRepositoryPrefix :: Maybe Text
$sel:ecrRepositoryPrefix:DeletePullThroughCacheRuleResponse' :: DeletePullThroughCacheRuleResponse -> Maybe Text
ecrRepositoryPrefix} -> Maybe Text
ecrRepositoryPrefix) (\s :: DeletePullThroughCacheRuleResponse
s@DeletePullThroughCacheRuleResponse' {} Maybe Text
a -> DeletePullThroughCacheRuleResponse
s {$sel:ecrRepositoryPrefix:DeletePullThroughCacheRuleResponse' :: Maybe Text
ecrRepositoryPrefix = Maybe Text
a} :: DeletePullThroughCacheRuleResponse)

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

-- | The upstream registry URL associated with the pull through cache rule.
deletePullThroughCacheRuleResponse_upstreamRegistryUrl :: Lens.Lens' DeletePullThroughCacheRuleResponse (Prelude.Maybe Prelude.Text)
deletePullThroughCacheRuleResponse_upstreamRegistryUrl :: Lens' DeletePullThroughCacheRuleResponse (Maybe Text)
deletePullThroughCacheRuleResponse_upstreamRegistryUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePullThroughCacheRuleResponse' {Maybe Text
upstreamRegistryUrl :: Maybe Text
$sel:upstreamRegistryUrl:DeletePullThroughCacheRuleResponse' :: DeletePullThroughCacheRuleResponse -> Maybe Text
upstreamRegistryUrl} -> Maybe Text
upstreamRegistryUrl) (\s :: DeletePullThroughCacheRuleResponse
s@DeletePullThroughCacheRuleResponse' {} Maybe Text
a -> DeletePullThroughCacheRuleResponse
s {$sel:upstreamRegistryUrl:DeletePullThroughCacheRuleResponse' :: Maybe Text
upstreamRegistryUrl = Maybe Text
a} :: DeletePullThroughCacheRuleResponse)

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

instance
  Prelude.NFData
    DeletePullThroughCacheRuleResponse
  where
  rnf :: DeletePullThroughCacheRuleResponse -> ()
rnf DeletePullThroughCacheRuleResponse' {Int
Maybe Text
Maybe POSIX
httpStatus :: Int
upstreamRegistryUrl :: Maybe Text
registryId :: Maybe Text
ecrRepositoryPrefix :: Maybe Text
createdAt :: Maybe POSIX
$sel:httpStatus:DeletePullThroughCacheRuleResponse' :: DeletePullThroughCacheRuleResponse -> Int
$sel:upstreamRegistryUrl:DeletePullThroughCacheRuleResponse' :: DeletePullThroughCacheRuleResponse -> Maybe Text
$sel:registryId:DeletePullThroughCacheRuleResponse' :: DeletePullThroughCacheRuleResponse -> Maybe Text
$sel:ecrRepositoryPrefix:DeletePullThroughCacheRuleResponse' :: DeletePullThroughCacheRuleResponse -> Maybe Text
$sel:createdAt:DeletePullThroughCacheRuleResponse' :: DeletePullThroughCacheRuleResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ecrRepositoryPrefix
      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
upstreamRegistryUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus