{-# 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.DeleteRegistryPolicy
-- 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 registry permissions policy.
module Amazonka.ECR.DeleteRegistryPolicy
  ( -- * Creating a Request
    DeleteRegistryPolicy (..),
    newDeleteRegistryPolicy,

    -- * Destructuring the Response
    DeleteRegistryPolicyResponse (..),
    newDeleteRegistryPolicyResponse,

    -- * Response Lenses
    deleteRegistryPolicyResponse_policyText,
    deleteRegistryPolicyResponse_registryId,
    deleteRegistryPolicyResponse_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:/ 'newDeleteRegistryPolicy' smart constructor.
data DeleteRegistryPolicy = DeleteRegistryPolicy'
  {
  }
  deriving (DeleteRegistryPolicy -> DeleteRegistryPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRegistryPolicy -> DeleteRegistryPolicy -> Bool
$c/= :: DeleteRegistryPolicy -> DeleteRegistryPolicy -> Bool
== :: DeleteRegistryPolicy -> DeleteRegistryPolicy -> Bool
$c== :: DeleteRegistryPolicy -> DeleteRegistryPolicy -> Bool
Prelude.Eq, ReadPrec [DeleteRegistryPolicy]
ReadPrec DeleteRegistryPolicy
Int -> ReadS DeleteRegistryPolicy
ReadS [DeleteRegistryPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRegistryPolicy]
$creadListPrec :: ReadPrec [DeleteRegistryPolicy]
readPrec :: ReadPrec DeleteRegistryPolicy
$creadPrec :: ReadPrec DeleteRegistryPolicy
readList :: ReadS [DeleteRegistryPolicy]
$creadList :: ReadS [DeleteRegistryPolicy]
readsPrec :: Int -> ReadS DeleteRegistryPolicy
$creadsPrec :: Int -> ReadS DeleteRegistryPolicy
Prelude.Read, Int -> DeleteRegistryPolicy -> ShowS
[DeleteRegistryPolicy] -> ShowS
DeleteRegistryPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRegistryPolicy] -> ShowS
$cshowList :: [DeleteRegistryPolicy] -> ShowS
show :: DeleteRegistryPolicy -> String
$cshow :: DeleteRegistryPolicy -> String
showsPrec :: Int -> DeleteRegistryPolicy -> ShowS
$cshowsPrec :: Int -> DeleteRegistryPolicy -> ShowS
Prelude.Show, forall x. Rep DeleteRegistryPolicy x -> DeleteRegistryPolicy
forall x. DeleteRegistryPolicy -> Rep DeleteRegistryPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteRegistryPolicy x -> DeleteRegistryPolicy
$cfrom :: forall x. DeleteRegistryPolicy -> Rep DeleteRegistryPolicy x
Prelude.Generic)

-- |
-- Create a value of 'DeleteRegistryPolicy' 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.
newDeleteRegistryPolicy ::
  DeleteRegistryPolicy
newDeleteRegistryPolicy :: DeleteRegistryPolicy
newDeleteRegistryPolicy = DeleteRegistryPolicy
DeleteRegistryPolicy'

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

instance Prelude.Hashable DeleteRegistryPolicy where
  hashWithSalt :: Int -> DeleteRegistryPolicy -> Int
hashWithSalt Int
_salt DeleteRegistryPolicy
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

instance Prelude.NFData DeleteRegistryPolicy where
  rnf :: DeleteRegistryPolicy -> ()
rnf DeleteRegistryPolicy
_ = ()

instance Data.ToHeaders DeleteRegistryPolicy where
  toHeaders :: DeleteRegistryPolicy -> 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.DeleteRegistryPolicy" ::
                          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 DeleteRegistryPolicy where
  toJSON :: DeleteRegistryPolicy -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

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

-- |
-- Create a value of 'DeleteRegistryPolicyResponse' 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', 'deleteRegistryPolicyResponse_policyText' - The contents of the registry permissions policy that was deleted.
--
-- 'registryId', 'deleteRegistryPolicyResponse_registryId' - The registry ID associated with the request.
--
-- 'httpStatus', 'deleteRegistryPolicyResponse_httpStatus' - The response's http status code.
newDeleteRegistryPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteRegistryPolicyResponse
newDeleteRegistryPolicyResponse :: Int -> DeleteRegistryPolicyResponse
newDeleteRegistryPolicyResponse Int
pHttpStatus_ =
  DeleteRegistryPolicyResponse'
    { $sel:policyText:DeleteRegistryPolicyResponse' :: Maybe Text
policyText =
        forall a. Maybe a
Prelude.Nothing,
      $sel:registryId:DeleteRegistryPolicyResponse' :: Maybe Text
registryId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteRegistryPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The contents of the registry permissions policy that was deleted.
deleteRegistryPolicyResponse_policyText :: Lens.Lens' DeleteRegistryPolicyResponse (Prelude.Maybe Prelude.Text)
deleteRegistryPolicyResponse_policyText :: Lens' DeleteRegistryPolicyResponse (Maybe Text)
deleteRegistryPolicyResponse_policyText = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRegistryPolicyResponse' {Maybe Text
policyText :: Maybe Text
$sel:policyText:DeleteRegistryPolicyResponse' :: DeleteRegistryPolicyResponse -> Maybe Text
policyText} -> Maybe Text
policyText) (\s :: DeleteRegistryPolicyResponse
s@DeleteRegistryPolicyResponse' {} Maybe Text
a -> DeleteRegistryPolicyResponse
s {$sel:policyText:DeleteRegistryPolicyResponse' :: Maybe Text
policyText = Maybe Text
a} :: DeleteRegistryPolicyResponse)

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

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

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