{-# 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.DeleteRepositoryPolicy
-- 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 the repository policy associated with the specified repository.
module Amazonka.ECR.DeleteRepositoryPolicy
  ( -- * Creating a Request
    DeleteRepositoryPolicy (..),
    newDeleteRepositoryPolicy,

    -- * Request Lenses
    deleteRepositoryPolicy_registryId,
    deleteRepositoryPolicy_repositoryName,

    -- * Destructuring the Response
    DeleteRepositoryPolicyResponse (..),
    newDeleteRepositoryPolicyResponse,

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

-- |
-- Create a value of 'DeleteRepositoryPolicy' 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', 'deleteRepositoryPolicy_registryId' - The Amazon Web Services account ID associated with the registry that
-- contains the repository policy to delete. If you do not specify a
-- registry, the default registry is assumed.
--
-- 'repositoryName', 'deleteRepositoryPolicy_repositoryName' - The name of the repository that is associated with the repository policy
-- to delete.
newDeleteRepositoryPolicy ::
  -- | 'repositoryName'
  Prelude.Text ->
  DeleteRepositoryPolicy
newDeleteRepositoryPolicy :: Text -> DeleteRepositoryPolicy
newDeleteRepositoryPolicy Text
pRepositoryName_ =
  DeleteRepositoryPolicy'
    { $sel:registryId:DeleteRepositoryPolicy' :: Maybe Text
registryId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:repositoryName:DeleteRepositoryPolicy' :: Text
repositoryName = Text
pRepositoryName_
    }

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

-- | The name of the repository that is associated with the repository policy
-- to delete.
deleteRepositoryPolicy_repositoryName :: Lens.Lens' DeleteRepositoryPolicy Prelude.Text
deleteRepositoryPolicy_repositoryName :: Lens' DeleteRepositoryPolicy Text
deleteRepositoryPolicy_repositoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRepositoryPolicy' {Text
repositoryName :: Text
$sel:repositoryName:DeleteRepositoryPolicy' :: DeleteRepositoryPolicy -> Text
repositoryName} -> Text
repositoryName) (\s :: DeleteRepositoryPolicy
s@DeleteRepositoryPolicy' {} Text
a -> DeleteRepositoryPolicy
s {$sel:repositoryName:DeleteRepositoryPolicy' :: Text
repositoryName = Text
a} :: DeleteRepositoryPolicy)

instance Core.AWSRequest DeleteRepositoryPolicy where
  type
    AWSResponse DeleteRepositoryPolicy =
      DeleteRepositoryPolicyResponse
  request :: (Service -> Service)
-> DeleteRepositoryPolicy -> Request DeleteRepositoryPolicy
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 DeleteRepositoryPolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteRepositoryPolicy)))
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 Text
-> Maybe Text
-> Maybe Text
-> Int
-> DeleteRepositoryPolicyResponse
DeleteRepositoryPolicyResponse'
            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
"policyText")
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DeleteRepositoryPolicy where
  hashWithSalt :: Int -> DeleteRepositoryPolicy -> Int
hashWithSalt Int
_salt DeleteRepositoryPolicy' {Maybe Text
Text
repositoryName :: Text
registryId :: Maybe Text
$sel:repositoryName:DeleteRepositoryPolicy' :: DeleteRepositoryPolicy -> Text
$sel:registryId:DeleteRepositoryPolicy' :: DeleteRepositoryPolicy -> 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

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

instance Data.ToHeaders DeleteRepositoryPolicy where
  toHeaders :: DeleteRepositoryPolicy -> 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.DeleteRepositoryPolicy" ::
                          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 DeleteRepositoryPolicy where
  toJSON :: DeleteRepositoryPolicy -> Value
toJSON DeleteRepositoryPolicy' {Maybe Text
Text
repositoryName :: Text
registryId :: Maybe Text
$sel:repositoryName:DeleteRepositoryPolicy' :: DeleteRepositoryPolicy -> Text
$sel:registryId:DeleteRepositoryPolicy' :: DeleteRepositoryPolicy -> 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)
          ]
      )

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

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

-- | /See:/ 'newDeleteRepositoryPolicyResponse' smart constructor.
data DeleteRepositoryPolicyResponse = DeleteRepositoryPolicyResponse'
  { -- | The JSON repository policy that was deleted from the repository.
    DeleteRepositoryPolicyResponse -> Maybe Text
policyText :: Prelude.Maybe Prelude.Text,
    -- | The registry ID associated with the request.
    DeleteRepositoryPolicyResponse -> Maybe Text
registryId :: Prelude.Maybe Prelude.Text,
    -- | The repository name associated with the request.
    DeleteRepositoryPolicyResponse -> Maybe Text
repositoryName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DeleteRepositoryPolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteRepositoryPolicyResponse
-> DeleteRepositoryPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRepositoryPolicyResponse
-> DeleteRepositoryPolicyResponse -> Bool
$c/= :: DeleteRepositoryPolicyResponse
-> DeleteRepositoryPolicyResponse -> Bool
== :: DeleteRepositoryPolicyResponse
-> DeleteRepositoryPolicyResponse -> Bool
$c== :: DeleteRepositoryPolicyResponse
-> DeleteRepositoryPolicyResponse -> Bool
Prelude.Eq, ReadPrec [DeleteRepositoryPolicyResponse]
ReadPrec DeleteRepositoryPolicyResponse
Int -> ReadS DeleteRepositoryPolicyResponse
ReadS [DeleteRepositoryPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRepositoryPolicyResponse]
$creadListPrec :: ReadPrec [DeleteRepositoryPolicyResponse]
readPrec :: ReadPrec DeleteRepositoryPolicyResponse
$creadPrec :: ReadPrec DeleteRepositoryPolicyResponse
readList :: ReadS [DeleteRepositoryPolicyResponse]
$creadList :: ReadS [DeleteRepositoryPolicyResponse]
readsPrec :: Int -> ReadS DeleteRepositoryPolicyResponse
$creadsPrec :: Int -> ReadS DeleteRepositoryPolicyResponse
Prelude.Read, Int -> DeleteRepositoryPolicyResponse -> ShowS
[DeleteRepositoryPolicyResponse] -> ShowS
DeleteRepositoryPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRepositoryPolicyResponse] -> ShowS
$cshowList :: [DeleteRepositoryPolicyResponse] -> ShowS
show :: DeleteRepositoryPolicyResponse -> String
$cshow :: DeleteRepositoryPolicyResponse -> String
showsPrec :: Int -> DeleteRepositoryPolicyResponse -> ShowS
$cshowsPrec :: Int -> DeleteRepositoryPolicyResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteRepositoryPolicyResponse x
-> DeleteRepositoryPolicyResponse
forall x.
DeleteRepositoryPolicyResponse
-> Rep DeleteRepositoryPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteRepositoryPolicyResponse x
-> DeleteRepositoryPolicyResponse
$cfrom :: forall x.
DeleteRepositoryPolicyResponse
-> Rep DeleteRepositoryPolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteRepositoryPolicyResponse' 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:
--
-- 'policyText', 'deleteRepositoryPolicyResponse_policyText' - The JSON repository policy that was deleted from the repository.
--
-- 'registryId', 'deleteRepositoryPolicyResponse_registryId' - The registry ID associated with the request.
--
-- 'repositoryName', 'deleteRepositoryPolicyResponse_repositoryName' - The repository name associated with the request.
--
-- 'httpStatus', 'deleteRepositoryPolicyResponse_httpStatus' - The response's http status code.
newDeleteRepositoryPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteRepositoryPolicyResponse
newDeleteRepositoryPolicyResponse :: Int -> DeleteRepositoryPolicyResponse
newDeleteRepositoryPolicyResponse Int
pHttpStatus_ =
  DeleteRepositoryPolicyResponse'
    { $sel:policyText:DeleteRepositoryPolicyResponse' :: Maybe Text
policyText =
        forall a. Maybe a
Prelude.Nothing,
      $sel:registryId:DeleteRepositoryPolicyResponse' :: Maybe Text
registryId = forall a. Maybe a
Prelude.Nothing,
      $sel:repositoryName:DeleteRepositoryPolicyResponse' :: Maybe Text
repositoryName = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteRepositoryPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The JSON repository policy that was deleted from the repository.
deleteRepositoryPolicyResponse_policyText :: Lens.Lens' DeleteRepositoryPolicyResponse (Prelude.Maybe Prelude.Text)
deleteRepositoryPolicyResponse_policyText :: Lens' DeleteRepositoryPolicyResponse (Maybe Text)
deleteRepositoryPolicyResponse_policyText = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRepositoryPolicyResponse' {Maybe Text
policyText :: Maybe Text
$sel:policyText:DeleteRepositoryPolicyResponse' :: DeleteRepositoryPolicyResponse -> Maybe Text
policyText} -> Maybe Text
policyText) (\s :: DeleteRepositoryPolicyResponse
s@DeleteRepositoryPolicyResponse' {} Maybe Text
a -> DeleteRepositoryPolicyResponse
s {$sel:policyText:DeleteRepositoryPolicyResponse' :: Maybe Text
policyText = Maybe Text
a} :: DeleteRepositoryPolicyResponse)

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

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

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

instance
  Prelude.NFData
    DeleteRepositoryPolicyResponse
  where
  rnf :: DeleteRepositoryPolicyResponse -> ()
rnf DeleteRepositoryPolicyResponse' {Int
Maybe Text
httpStatus :: Int
repositoryName :: Maybe Text
registryId :: Maybe Text
policyText :: Maybe Text
$sel:httpStatus:DeleteRepositoryPolicyResponse' :: DeleteRepositoryPolicyResponse -> Int
$sel:repositoryName:DeleteRepositoryPolicyResponse' :: DeleteRepositoryPolicyResponse -> Maybe Text
$sel:registryId:DeleteRepositoryPolicyResponse' :: DeleteRepositoryPolicyResponse -> Maybe Text
$sel:policyText:DeleteRepositoryPolicyResponse' :: DeleteRepositoryPolicyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyText
      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 Int
httpStatus