{-# 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.TagResource
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Add tags to the specified Amazon SNS topic. For an overview, see
-- <https://docs.aws.amazon.com/sns/latest/dg/sns-tags.html Amazon SNS Tags>
-- in the /Amazon SNS Developer Guide/.
--
-- When you use topic tags, keep the following guidelines in mind:
--
-- -   Adding more than 50 tags to a topic isn\'t recommended.
--
-- -   Tags don\'t have any semantic meaning. Amazon SNS interprets tags as
--     character strings.
--
-- -   Tags are case-sensitive.
--
-- -   A new tag with a key identical to that of an existing tag overwrites
--     the existing tag.
--
-- -   Tagging actions are limited to 10 TPS per Amazon Web Services
--     account, per Amazon Web Services Region. If your application
--     requires a higher throughput, file a
--     <https://console.aws.amazon.com/support/home#/case/create?issueType=technical technical support request>.
module Amazonka.SNS.TagResource
  ( -- * Creating a Request
    TagResource (..),
    newTagResource,

    -- * Request Lenses
    tagResource_resourceArn,
    tagResource_tags,

    -- * Destructuring the Response
    TagResourceResponse (..),
    newTagResourceResponse,

    -- * Response Lenses
    tagResourceResponse_httpStatus,
  )
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:/ 'newTagResource' smart constructor.
data TagResource = TagResource'
  { -- | The ARN of the topic to which to add tags.
    TagResource -> Text
resourceArn :: Prelude.Text,
    -- | The tags to be added to the specified topic. A tag consists of a
    -- required key and an optional value.
    TagResource -> [Tag]
tags :: [Tag]
  }
  deriving (TagResource -> TagResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TagResource -> TagResource -> Bool
$c/= :: TagResource -> TagResource -> Bool
== :: TagResource -> TagResource -> Bool
$c== :: TagResource -> TagResource -> Bool
Prelude.Eq, ReadPrec [TagResource]
ReadPrec TagResource
Int -> ReadS TagResource
ReadS [TagResource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TagResource]
$creadListPrec :: ReadPrec [TagResource]
readPrec :: ReadPrec TagResource
$creadPrec :: ReadPrec TagResource
readList :: ReadS [TagResource]
$creadList :: ReadS [TagResource]
readsPrec :: Int -> ReadS TagResource
$creadsPrec :: Int -> ReadS TagResource
Prelude.Read, Int -> TagResource -> ShowS
[TagResource] -> ShowS
TagResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TagResource] -> ShowS
$cshowList :: [TagResource] -> ShowS
show :: TagResource -> String
$cshow :: TagResource -> String
showsPrec :: Int -> TagResource -> ShowS
$cshowsPrec :: Int -> TagResource -> ShowS
Prelude.Show, forall x. Rep TagResource x -> TagResource
forall x. TagResource -> Rep TagResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TagResource x -> TagResource
$cfrom :: forall x. TagResource -> Rep TagResource x
Prelude.Generic)

-- |
-- Create a value of 'TagResource' 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:
--
-- 'resourceArn', 'tagResource_resourceArn' - The ARN of the topic to which to add tags.
--
-- 'tags', 'tagResource_tags' - The tags to be added to the specified topic. A tag consists of a
-- required key and an optional value.
newTagResource ::
  -- | 'resourceArn'
  Prelude.Text ->
  TagResource
newTagResource :: Text -> TagResource
newTagResource Text
pResourceArn_ =
  TagResource'
    { $sel:resourceArn:TagResource' :: Text
resourceArn = Text
pResourceArn_,
      $sel:tags:TagResource' :: [Tag]
tags = forall a. Monoid a => a
Prelude.mempty
    }

-- | The ARN of the topic to which to add tags.
tagResource_resourceArn :: Lens.Lens' TagResource Prelude.Text
tagResource_resourceArn :: Lens' TagResource Text
tagResource_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagResource' {Text
resourceArn :: Text
$sel:resourceArn:TagResource' :: TagResource -> Text
resourceArn} -> Text
resourceArn) (\s :: TagResource
s@TagResource' {} Text
a -> TagResource
s {$sel:resourceArn:TagResource' :: Text
resourceArn = Text
a} :: TagResource)

-- | The tags to be added to the specified topic. A tag consists of a
-- required key and an optional value.
tagResource_tags :: Lens.Lens' TagResource [Tag]
tagResource_tags :: Lens' TagResource [Tag]
tagResource_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagResource' {[Tag]
tags :: [Tag]
$sel:tags:TagResource' :: TagResource -> [Tag]
tags} -> [Tag]
tags) (\s :: TagResource
s@TagResource' {} [Tag]
a -> TagResource
s {$sel:tags:TagResource' :: [Tag]
tags = [Tag]
a} :: TagResource) 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 TagResource where
  type AWSResponse TagResource = TagResourceResponse
  request :: (Service -> Service) -> TagResource -> Request TagResource
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 TagResource
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse TagResource)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"TagResourceResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> TagResourceResponse
TagResourceResponse'
            forall (f :: * -> *) a b. Functor 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 TagResource where
  hashWithSalt :: Int -> TagResource -> Int
hashWithSalt Int
_salt TagResource' {[Tag]
Text
tags :: [Tag]
resourceArn :: Text
$sel:tags:TagResource' :: TagResource -> [Tag]
$sel:resourceArn:TagResource' :: TagResource -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Tag]
tags

instance Prelude.NFData TagResource where
  rnf :: TagResource -> ()
rnf TagResource' {[Tag]
Text
tags :: [Tag]
resourceArn :: Text
$sel:tags:TagResource' :: TagResource -> [Tag]
$sel:resourceArn:TagResource' :: TagResource -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Tag]
tags

instance Data.ToHeaders TagResource where
  toHeaders :: TagResource -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery TagResource where
  toQuery :: TagResource -> QueryString
toQuery TagResource' {[Tag]
Text
tags :: [Tag]
resourceArn :: Text
$sel:tags:TagResource' :: TagResource -> [Tag]
$sel:resourceArn:TagResource' :: TagResource -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"TagResource" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-03-31" :: Prelude.ByteString),
        ByteString
"ResourceArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
resourceArn,
        ByteString
"Tags" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Tag]
tags
      ]

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

-- |
-- Create a value of 'TagResourceResponse' 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:
--
-- 'httpStatus', 'tagResourceResponse_httpStatus' - The response's http status code.
newTagResourceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  TagResourceResponse
newTagResourceResponse :: Int -> TagResourceResponse
newTagResourceResponse Int
pHttpStatus_ =
  TagResourceResponse' {$sel:httpStatus:TagResourceResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData TagResourceResponse where
  rnf :: TagResourceResponse -> ()
rnf TagResourceResponse' {Int
httpStatus :: Int
$sel:httpStatus:TagResourceResponse' :: TagResourceResponse -> Int
..} = forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus