{-# 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.SQS.RemovePermission
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Revokes any permissions in the queue policy that matches the specified
-- @Label@ parameter.
--
-- -   Only the owner of a queue can remove permissions from it.
--
-- -   Cross-account permissions don\'t apply to this action. For more
--     information, see
--     <https://docs.aws.amazon.com/AWSSimpleQueueService/latest/SQSDeveloperGuide/sqs-customer-managed-policy-examples.html#grant-cross-account-permissions-to-role-and-user-name Grant cross-account permissions to a role and a user name>
--     in the /Amazon SQS Developer Guide/.
--
-- -   To remove the ability to change queue permissions, you must deny
--     permission to the @AddPermission@, @RemovePermission@, and
--     @SetQueueAttributes@ actions in your IAM policy.
module Amazonka.SQS.RemovePermission
  ( -- * Creating a Request
    RemovePermission (..),
    newRemovePermission,

    -- * Request Lenses
    removePermission_queueUrl,
    removePermission_label,

    -- * Destructuring the Response
    RemovePermissionResponse (..),
    newRemovePermissionResponse,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SQS.Types

-- |
--
-- /See:/ 'newRemovePermission' smart constructor.
data RemovePermission = RemovePermission'
  { -- | The URL of the Amazon SQS queue from which permissions are removed.
    --
    -- Queue URLs and names are case-sensitive.
    RemovePermission -> Text
queueUrl :: Prelude.Text,
    -- | The identification of the permission to remove. This is the label added
    -- using the @ @@AddPermission@@ @ action.
    RemovePermission -> Text
label :: Prelude.Text
  }
  deriving (RemovePermission -> RemovePermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemovePermission -> RemovePermission -> Bool
$c/= :: RemovePermission -> RemovePermission -> Bool
== :: RemovePermission -> RemovePermission -> Bool
$c== :: RemovePermission -> RemovePermission -> Bool
Prelude.Eq, ReadPrec [RemovePermission]
ReadPrec RemovePermission
Int -> ReadS RemovePermission
ReadS [RemovePermission]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemovePermission]
$creadListPrec :: ReadPrec [RemovePermission]
readPrec :: ReadPrec RemovePermission
$creadPrec :: ReadPrec RemovePermission
readList :: ReadS [RemovePermission]
$creadList :: ReadS [RemovePermission]
readsPrec :: Int -> ReadS RemovePermission
$creadsPrec :: Int -> ReadS RemovePermission
Prelude.Read, Int -> RemovePermission -> ShowS
[RemovePermission] -> ShowS
RemovePermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemovePermission] -> ShowS
$cshowList :: [RemovePermission] -> ShowS
show :: RemovePermission -> String
$cshow :: RemovePermission -> String
showsPrec :: Int -> RemovePermission -> ShowS
$cshowsPrec :: Int -> RemovePermission -> ShowS
Prelude.Show, forall x. Rep RemovePermission x -> RemovePermission
forall x. RemovePermission -> Rep RemovePermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemovePermission x -> RemovePermission
$cfrom :: forall x. RemovePermission -> Rep RemovePermission x
Prelude.Generic)

-- |
-- Create a value of 'RemovePermission' 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:
--
-- 'queueUrl', 'removePermission_queueUrl' - The URL of the Amazon SQS queue from which permissions are removed.
--
-- Queue URLs and names are case-sensitive.
--
-- 'label', 'removePermission_label' - The identification of the permission to remove. This is the label added
-- using the @ @@AddPermission@@ @ action.
newRemovePermission ::
  -- | 'queueUrl'
  Prelude.Text ->
  -- | 'label'
  Prelude.Text ->
  RemovePermission
newRemovePermission :: Text -> Text -> RemovePermission
newRemovePermission Text
pQueueUrl_ Text
pLabel_ =
  RemovePermission'
    { $sel:queueUrl:RemovePermission' :: Text
queueUrl = Text
pQueueUrl_,
      $sel:label:RemovePermission' :: Text
label = Text
pLabel_
    }

-- | The URL of the Amazon SQS queue from which permissions are removed.
--
-- Queue URLs and names are case-sensitive.
removePermission_queueUrl :: Lens.Lens' RemovePermission Prelude.Text
removePermission_queueUrl :: Lens' RemovePermission Text
removePermission_queueUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemovePermission' {Text
queueUrl :: Text
$sel:queueUrl:RemovePermission' :: RemovePermission -> Text
queueUrl} -> Text
queueUrl) (\s :: RemovePermission
s@RemovePermission' {} Text
a -> RemovePermission
s {$sel:queueUrl:RemovePermission' :: Text
queueUrl = Text
a} :: RemovePermission)

-- | The identification of the permission to remove. This is the label added
-- using the @ @@AddPermission@@ @ action.
removePermission_label :: Lens.Lens' RemovePermission Prelude.Text
removePermission_label :: Lens' RemovePermission Text
removePermission_label = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemovePermission' {Text
label :: Text
$sel:label:RemovePermission' :: RemovePermission -> Text
label} -> Text
label) (\s :: RemovePermission
s@RemovePermission' {} Text
a -> RemovePermission
s {$sel:label:RemovePermission' :: Text
label = Text
a} :: RemovePermission)

instance Core.AWSRequest RemovePermission where
  type
    AWSResponse RemovePermission =
      RemovePermissionResponse
  request :: (Service -> Service)
-> RemovePermission -> Request RemovePermission
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy RemovePermission
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse RemovePermission)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull RemovePermissionResponse
RemovePermissionResponse'

instance Prelude.Hashable RemovePermission where
  hashWithSalt :: Int -> RemovePermission -> Int
hashWithSalt Int
_salt RemovePermission' {Text
label :: Text
queueUrl :: Text
$sel:label:RemovePermission' :: RemovePermission -> Text
$sel:queueUrl:RemovePermission' :: RemovePermission -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
queueUrl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
label

instance Prelude.NFData RemovePermission where
  rnf :: RemovePermission -> ()
rnf RemovePermission' {Text
label :: Text
queueUrl :: Text
$sel:label:RemovePermission' :: RemovePermission -> Text
$sel:queueUrl:RemovePermission' :: RemovePermission -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
queueUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
label

instance Data.ToHeaders RemovePermission where
  toHeaders :: RemovePermission -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery RemovePermission where
  toQuery :: RemovePermission -> QueryString
toQuery RemovePermission' {Text
label :: Text
queueUrl :: Text
$sel:label:RemovePermission' :: RemovePermission -> Text
$sel:queueUrl:RemovePermission' :: RemovePermission -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"RemovePermission" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-11-05" :: Prelude.ByteString),
        ByteString
"QueueUrl" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
queueUrl,
        ByteString
"Label" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
label
      ]

-- | /See:/ 'newRemovePermissionResponse' smart constructor.
data RemovePermissionResponse = RemovePermissionResponse'
  {
  }
  deriving (RemovePermissionResponse -> RemovePermissionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemovePermissionResponse -> RemovePermissionResponse -> Bool
$c/= :: RemovePermissionResponse -> RemovePermissionResponse -> Bool
== :: RemovePermissionResponse -> RemovePermissionResponse -> Bool
$c== :: RemovePermissionResponse -> RemovePermissionResponse -> Bool
Prelude.Eq, ReadPrec [RemovePermissionResponse]
ReadPrec RemovePermissionResponse
Int -> ReadS RemovePermissionResponse
ReadS [RemovePermissionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemovePermissionResponse]
$creadListPrec :: ReadPrec [RemovePermissionResponse]
readPrec :: ReadPrec RemovePermissionResponse
$creadPrec :: ReadPrec RemovePermissionResponse
readList :: ReadS [RemovePermissionResponse]
$creadList :: ReadS [RemovePermissionResponse]
readsPrec :: Int -> ReadS RemovePermissionResponse
$creadsPrec :: Int -> ReadS RemovePermissionResponse
Prelude.Read, Int -> RemovePermissionResponse -> ShowS
[RemovePermissionResponse] -> ShowS
RemovePermissionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemovePermissionResponse] -> ShowS
$cshowList :: [RemovePermissionResponse] -> ShowS
show :: RemovePermissionResponse -> String
$cshow :: RemovePermissionResponse -> String
showsPrec :: Int -> RemovePermissionResponse -> ShowS
$cshowsPrec :: Int -> RemovePermissionResponse -> ShowS
Prelude.Show, forall x.
Rep RemovePermissionResponse x -> RemovePermissionResponse
forall x.
RemovePermissionResponse -> Rep RemovePermissionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemovePermissionResponse x -> RemovePermissionResponse
$cfrom :: forall x.
RemovePermissionResponse -> Rep RemovePermissionResponse x
Prelude.Generic)

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

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