{-# 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.ResourceGroups.Tag
-- 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 tags to a resource group with the specified ARN. Existing tags on a
-- resource group are not changed if they are not specified in the request
-- parameters.
--
-- Do not store personally identifiable information (PII) or other
-- confidential or sensitive information in tags. We use tags to provide
-- you with billing and administration services. Tags are not intended to
-- be used for private or sensitive data.
--
-- __Minimum permissions__
--
-- To run this command, you must have the following permissions:
--
-- -   @resource-groups:Tag@
module Amazonka.ResourceGroups.Tag
  ( -- * Creating a Request
    Tag (..),
    newTag,

    -- * Request Lenses
    tag_arn,
    tag_tags,

    -- * Destructuring the Response
    TagResponse (..),
    newTagResponse,

    -- * Response Lenses
    tagResponse_arn,
    tagResponse_tags,
    tagResponse_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 Amazonka.ResourceGroups.Types
import qualified Amazonka.Response as Response

-- | /See:/ 'newTag' smart constructor.
data Tag = Tag'
  { -- | The ARN of the resource group to which to add tags.
    Tag -> Text
arn :: Prelude.Text,
    -- | The tags to add to the specified resource group. A tag is a
    -- string-to-string map of key-value pairs.
    Tag -> HashMap Text Text
tags :: Prelude.HashMap Prelude.Text Prelude.Text
  }
  deriving (Tag -> Tag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tag -> Tag -> Bool
$c/= :: Tag -> Tag -> Bool
== :: Tag -> Tag -> Bool
$c== :: Tag -> Tag -> Bool
Prelude.Eq, ReadPrec [Tag]
ReadPrec Tag
Int -> ReadS Tag
ReadS [Tag]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Tag]
$creadListPrec :: ReadPrec [Tag]
readPrec :: ReadPrec Tag
$creadPrec :: ReadPrec Tag
readList :: ReadS [Tag]
$creadList :: ReadS [Tag]
readsPrec :: Int -> ReadS Tag
$creadsPrec :: Int -> ReadS Tag
Prelude.Read, Int -> Tag -> ShowS
[Tag] -> ShowS
Tag -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tag] -> ShowS
$cshowList :: [Tag] -> ShowS
show :: Tag -> String
$cshow :: Tag -> String
showsPrec :: Int -> Tag -> ShowS
$cshowsPrec :: Int -> Tag -> ShowS
Prelude.Show, forall x. Rep Tag x -> Tag
forall x. Tag -> Rep Tag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tag x -> Tag
$cfrom :: forall x. Tag -> Rep Tag x
Prelude.Generic)

-- |
-- Create a value of 'Tag' 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:
--
-- 'arn', 'tag_arn' - The ARN of the resource group to which to add tags.
--
-- 'tags', 'tag_tags' - The tags to add to the specified resource group. A tag is a
-- string-to-string map of key-value pairs.
newTag ::
  -- | 'arn'
  Prelude.Text ->
  Tag
newTag :: Text -> Tag
newTag Text
pArn_ =
  Tag' {$sel:arn:Tag' :: Text
arn = Text
pArn_, $sel:tags:Tag' :: HashMap Text Text
tags = forall a. Monoid a => a
Prelude.mempty}

-- | The ARN of the resource group to which to add tags.
tag_arn :: Lens.Lens' Tag Prelude.Text
tag_arn :: Lens' Tag Text
tag_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Tag' {Text
arn :: Text
$sel:arn:Tag' :: Tag -> Text
arn} -> Text
arn) (\s :: Tag
s@Tag' {} Text
a -> Tag
s {$sel:arn:Tag' :: Text
arn = Text
a} :: Tag)

-- | The tags to add to the specified resource group. A tag is a
-- string-to-string map of key-value pairs.
tag_tags :: Lens.Lens' Tag (Prelude.HashMap Prelude.Text Prelude.Text)
tag_tags :: Lens' Tag (HashMap Text Text)
tag_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Tag' {HashMap Text Text
tags :: HashMap Text Text
$sel:tags:Tag' :: Tag -> HashMap Text Text
tags} -> HashMap Text Text
tags) (\s :: Tag
s@Tag' {} HashMap Text Text
a -> Tag
s {$sel:tags:Tag' :: HashMap Text Text
tags = HashMap Text Text
a} :: Tag) 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 Tag where
  type AWSResponse Tag = TagResponse
  request :: (Service -> Service) -> Tag -> Request Tag
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy Tag
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse Tag)))
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 (HashMap Text Text) -> Int -> TagResponse
TagResponse'
            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
"Arn")
            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
"Tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 Tag where
  hashWithSalt :: Int -> Tag -> Int
hashWithSalt Int
_salt Tag' {Text
HashMap Text Text
tags :: HashMap Text Text
arn :: Text
$sel:tags:Tag' :: Tag -> HashMap Text Text
$sel:arn:Tag' :: Tag -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HashMap Text Text
tags

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

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

instance Data.ToJSON Tag where
  toJSON :: Tag -> Value
toJSON Tag' {Text
HashMap Text Text
tags :: HashMap Text Text
arn :: Text
$sel:tags:Tag' :: Tag -> HashMap Text Text
$sel:arn:Tag' :: Tag -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= HashMap Text Text
tags)]
      )

instance Data.ToPath Tag where
  toPath :: Tag -> ByteString
toPath Tag' {Text
HashMap Text Text
tags :: HashMap Text Text
arn :: Text
$sel:tags:Tag' :: Tag -> HashMap Text Text
$sel:arn:Tag' :: Tag -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/resources/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
arn, ByteString
"/tags"]

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

-- | /See:/ 'newTagResponse' smart constructor.
data TagResponse = TagResponse'
  { -- | The ARN of the tagged resource.
    TagResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The tags that have been added to the specified resource group.
    TagResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    TagResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (TagResponse -> TagResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TagResponse -> TagResponse -> Bool
$c/= :: TagResponse -> TagResponse -> Bool
== :: TagResponse -> TagResponse -> Bool
$c== :: TagResponse -> TagResponse -> Bool
Prelude.Eq, ReadPrec [TagResponse]
ReadPrec TagResponse
Int -> ReadS TagResponse
ReadS [TagResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TagResponse]
$creadListPrec :: ReadPrec [TagResponse]
readPrec :: ReadPrec TagResponse
$creadPrec :: ReadPrec TagResponse
readList :: ReadS [TagResponse]
$creadList :: ReadS [TagResponse]
readsPrec :: Int -> ReadS TagResponse
$creadsPrec :: Int -> ReadS TagResponse
Prelude.Read, Int -> TagResponse -> ShowS
[TagResponse] -> ShowS
TagResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TagResponse] -> ShowS
$cshowList :: [TagResponse] -> ShowS
show :: TagResponse -> String
$cshow :: TagResponse -> String
showsPrec :: Int -> TagResponse -> ShowS
$cshowsPrec :: Int -> TagResponse -> ShowS
Prelude.Show, forall x. Rep TagResponse x -> TagResponse
forall x. TagResponse -> Rep TagResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TagResponse x -> TagResponse
$cfrom :: forall x. TagResponse -> Rep TagResponse x
Prelude.Generic)

-- |
-- Create a value of 'TagResponse' 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:
--
-- 'arn', 'tagResponse_arn' - The ARN of the tagged resource.
--
-- 'tags', 'tagResponse_tags' - The tags that have been added to the specified resource group.
--
-- 'httpStatus', 'tagResponse_httpStatus' - The response's http status code.
newTagResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  TagResponse
newTagResponse :: Int -> TagResponse
newTagResponse Int
pHttpStatus_ =
  TagResponse'
    { $sel:arn:TagResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:TagResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:TagResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the tagged resource.
tagResponse_arn :: Lens.Lens' TagResponse (Prelude.Maybe Prelude.Text)
tagResponse_arn :: Lens' TagResponse (Maybe Text)
tagResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:TagResponse' :: TagResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: TagResponse
s@TagResponse' {} Maybe Text
a -> TagResponse
s {$sel:arn:TagResponse' :: Maybe Text
arn = Maybe Text
a} :: TagResponse)

-- | The tags that have been added to the specified resource group.
tagResponse_tags :: Lens.Lens' TagResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
tagResponse_tags :: Lens' TagResponse (Maybe (HashMap Text Text))
tagResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:TagResponse' :: TagResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: TagResponse
s@TagResponse' {} Maybe (HashMap Text Text)
a -> TagResponse
s {$sel:tags:TagResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: TagResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData TagResponse where
  rnf :: TagResponse -> ()
rnf TagResponse' {Int
Maybe Text
Maybe (HashMap Text Text)
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
arn :: Maybe Text
$sel:httpStatus:TagResponse' :: TagResponse -> Int
$sel:tags:TagResponse' :: TagResponse -> Maybe (HashMap Text Text)
$sel:arn:TagResponse' :: TagResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus