{-# 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.SNS.AddPermission
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds a statement to a topic\'s access control policy, granting access
-- for the specified Amazon Web Services accounts to the specified actions.
--
-- To remove the ability to change topic permissions, you must deny
-- permissions to the @AddPermission@, @RemovePermission@, and
-- @SetTopicAttributes@ actions in your IAM policy.
module Amazonka.SNS.AddPermission
  ( -- * Creating a Request
    AddPermission (..),
    newAddPermission,

    -- * Request Lenses
    addPermission_topicArn,
    addPermission_label,
    addPermission_aWSAccountId,
    addPermission_actionName,

    -- * Destructuring the Response
    AddPermissionResponse (..),
    newAddPermissionResponse,
  )
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.SNS.Types

-- | /See:/ 'newAddPermission' smart constructor.
data AddPermission = AddPermission'
  { -- | The ARN of the topic whose access control policy you wish to modify.
    AddPermission -> Text
topicArn :: Prelude.Text,
    -- | A unique identifier for the new policy statement.
    AddPermission -> Text
label :: Prelude.Text,
    -- | The Amazon Web Services account IDs of the users (principals) who will
    -- be given access to the specified actions. The users must have Amazon Web
    -- Services account, but do not need to be signed up for this service.
    AddPermission -> [Text]
aWSAccountId :: [Prelude.Text],
    -- | The action you want to allow for the specified principal(s).
    --
    -- Valid values: Any Amazon SNS action name, for example @Publish@.
    AddPermission -> [Text]
actionName :: [Prelude.Text]
  }
  deriving (AddPermission -> AddPermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddPermission -> AddPermission -> Bool
$c/= :: AddPermission -> AddPermission -> Bool
== :: AddPermission -> AddPermission -> Bool
$c== :: AddPermission -> AddPermission -> Bool
Prelude.Eq, ReadPrec [AddPermission]
ReadPrec AddPermission
Int -> ReadS AddPermission
ReadS [AddPermission]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddPermission]
$creadListPrec :: ReadPrec [AddPermission]
readPrec :: ReadPrec AddPermission
$creadPrec :: ReadPrec AddPermission
readList :: ReadS [AddPermission]
$creadList :: ReadS [AddPermission]
readsPrec :: Int -> ReadS AddPermission
$creadsPrec :: Int -> ReadS AddPermission
Prelude.Read, Int -> AddPermission -> ShowS
[AddPermission] -> ShowS
AddPermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddPermission] -> ShowS
$cshowList :: [AddPermission] -> ShowS
show :: AddPermission -> String
$cshow :: AddPermission -> String
showsPrec :: Int -> AddPermission -> ShowS
$cshowsPrec :: Int -> AddPermission -> ShowS
Prelude.Show, forall x. Rep AddPermission x -> AddPermission
forall x. AddPermission -> Rep AddPermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddPermission x -> AddPermission
$cfrom :: forall x. AddPermission -> Rep AddPermission x
Prelude.Generic)

-- |
-- Create a value of 'AddPermission' 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:
--
-- 'topicArn', 'addPermission_topicArn' - The ARN of the topic whose access control policy you wish to modify.
--
-- 'label', 'addPermission_label' - A unique identifier for the new policy statement.
--
-- 'aWSAccountId', 'addPermission_aWSAccountId' - The Amazon Web Services account IDs of the users (principals) who will
-- be given access to the specified actions. The users must have Amazon Web
-- Services account, but do not need to be signed up for this service.
--
-- 'actionName', 'addPermission_actionName' - The action you want to allow for the specified principal(s).
--
-- Valid values: Any Amazon SNS action name, for example @Publish@.
newAddPermission ::
  -- | 'topicArn'
  Prelude.Text ->
  -- | 'label'
  Prelude.Text ->
  AddPermission
newAddPermission :: Text -> Text -> AddPermission
newAddPermission Text
pTopicArn_ Text
pLabel_ =
  AddPermission'
    { $sel:topicArn:AddPermission' :: Text
topicArn = Text
pTopicArn_,
      $sel:label:AddPermission' :: Text
label = Text
pLabel_,
      $sel:aWSAccountId:AddPermission' :: [Text]
aWSAccountId = forall a. Monoid a => a
Prelude.mempty,
      $sel:actionName:AddPermission' :: [Text]
actionName = forall a. Monoid a => a
Prelude.mempty
    }

-- | The ARN of the topic whose access control policy you wish to modify.
addPermission_topicArn :: Lens.Lens' AddPermission Prelude.Text
addPermission_topicArn :: Lens' AddPermission Text
addPermission_topicArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddPermission' {Text
topicArn :: Text
$sel:topicArn:AddPermission' :: AddPermission -> Text
topicArn} -> Text
topicArn) (\s :: AddPermission
s@AddPermission' {} Text
a -> AddPermission
s {$sel:topicArn:AddPermission' :: Text
topicArn = Text
a} :: AddPermission)

-- | A unique identifier for the new policy statement.
addPermission_label :: Lens.Lens' AddPermission Prelude.Text
addPermission_label :: Lens' AddPermission Text
addPermission_label = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddPermission' {Text
label :: Text
$sel:label:AddPermission' :: AddPermission -> Text
label} -> Text
label) (\s :: AddPermission
s@AddPermission' {} Text
a -> AddPermission
s {$sel:label:AddPermission' :: Text
label = Text
a} :: AddPermission)

-- | The Amazon Web Services account IDs of the users (principals) who will
-- be given access to the specified actions. The users must have Amazon Web
-- Services account, but do not need to be signed up for this service.
addPermission_aWSAccountId :: Lens.Lens' AddPermission [Prelude.Text]
addPermission_aWSAccountId :: Lens' AddPermission [Text]
addPermission_aWSAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddPermission' {[Text]
aWSAccountId :: [Text]
$sel:aWSAccountId:AddPermission' :: AddPermission -> [Text]
aWSAccountId} -> [Text]
aWSAccountId) (\s :: AddPermission
s@AddPermission' {} [Text]
a -> AddPermission
s {$sel:aWSAccountId:AddPermission' :: [Text]
aWSAccountId = [Text]
a} :: AddPermission) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The action you want to allow for the specified principal(s).
--
-- Valid values: Any Amazon SNS action name, for example @Publish@.
addPermission_actionName :: Lens.Lens' AddPermission [Prelude.Text]
addPermission_actionName :: Lens' AddPermission [Text]
addPermission_actionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddPermission' {[Text]
actionName :: [Text]
$sel:actionName:AddPermission' :: AddPermission -> [Text]
actionName} -> [Text]
actionName) (\s :: AddPermission
s@AddPermission' {} [Text]
a -> AddPermission
s {$sel:actionName:AddPermission' :: [Text]
actionName = [Text]
a} :: AddPermission) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest AddPermission where
  type
    AWSResponse AddPermission =
      AddPermissionResponse
  request :: (Service -> Service) -> AddPermission -> Request AddPermission
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 AddPermission
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AddPermission)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull AddPermissionResponse
AddPermissionResponse'

instance Prelude.Hashable AddPermission where
  hashWithSalt :: Int -> AddPermission -> Int
hashWithSalt Int
_salt AddPermission' {[Text]
Text
actionName :: [Text]
aWSAccountId :: [Text]
label :: Text
topicArn :: Text
$sel:actionName:AddPermission' :: AddPermission -> [Text]
$sel:aWSAccountId:AddPermission' :: AddPermission -> [Text]
$sel:label:AddPermission' :: AddPermission -> Text
$sel:topicArn:AddPermission' :: AddPermission -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
topicArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
label
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
aWSAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
actionName

instance Prelude.NFData AddPermission where
  rnf :: AddPermission -> ()
rnf AddPermission' {[Text]
Text
actionName :: [Text]
aWSAccountId :: [Text]
label :: Text
topicArn :: Text
$sel:actionName:AddPermission' :: AddPermission -> [Text]
$sel:aWSAccountId:AddPermission' :: AddPermission -> [Text]
$sel:label:AddPermission' :: AddPermission -> Text
$sel:topicArn:AddPermission' :: AddPermission -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
topicArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
label
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
aWSAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
actionName

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

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

instance Data.ToQuery AddPermission where
  toQuery :: AddPermission -> QueryString
toQuery AddPermission' {[Text]
Text
actionName :: [Text]
aWSAccountId :: [Text]
label :: Text
topicArn :: Text
$sel:actionName:AddPermission' :: AddPermission -> [Text]
$sel:aWSAccountId:AddPermission' :: AddPermission -> [Text]
$sel:label:AddPermission' :: AddPermission -> Text
$sel:topicArn:AddPermission' :: AddPermission -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"AddPermission" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-03-31" :: Prelude.ByteString),
        ByteString
"TopicArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
topicArn,
        ByteString
"Label" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
label,
        ByteString
"AWSAccountId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Text]
aWSAccountId,
        ByteString
"ActionName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Text]
actionName
      ]

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

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

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