{-# 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.GetTags
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of tags that are associated with a resource group,
-- specified by an ARN.
--
-- __Minimum permissions__
--
-- To run this command, you must have the following permissions:
--
-- -   @resource-groups:GetTags@
module Amazonka.ResourceGroups.GetTags
  ( -- * Creating a Request
    GetTags (..),
    newGetTags,

    -- * Request Lenses
    getTags_arn,

    -- * Destructuring the Response
    GetTagsResponse (..),
    newGetTagsResponse,

    -- * Response Lenses
    getTagsResponse_arn,
    getTagsResponse_tags,
    getTagsResponse_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:/ 'newGetTags' smart constructor.
data GetTags = GetTags'
  { -- | The ARN of the resource group whose tags you want to retrieve.
    GetTags -> Text
arn :: Prelude.Text
  }
  deriving (GetTags -> GetTags -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTags -> GetTags -> Bool
$c/= :: GetTags -> GetTags -> Bool
== :: GetTags -> GetTags -> Bool
$c== :: GetTags -> GetTags -> Bool
Prelude.Eq, ReadPrec [GetTags]
ReadPrec GetTags
Int -> ReadS GetTags
ReadS [GetTags]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTags]
$creadListPrec :: ReadPrec [GetTags]
readPrec :: ReadPrec GetTags
$creadPrec :: ReadPrec GetTags
readList :: ReadS [GetTags]
$creadList :: ReadS [GetTags]
readsPrec :: Int -> ReadS GetTags
$creadsPrec :: Int -> ReadS GetTags
Prelude.Read, Int -> GetTags -> ShowS
[GetTags] -> ShowS
GetTags -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTags] -> ShowS
$cshowList :: [GetTags] -> ShowS
show :: GetTags -> String
$cshow :: GetTags -> String
showsPrec :: Int -> GetTags -> ShowS
$cshowsPrec :: Int -> GetTags -> ShowS
Prelude.Show, forall x. Rep GetTags x -> GetTags
forall x. GetTags -> Rep GetTags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTags x -> GetTags
$cfrom :: forall x. GetTags -> Rep GetTags x
Prelude.Generic)

-- |
-- Create a value of 'GetTags' 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', 'getTags_arn' - The ARN of the resource group whose tags you want to retrieve.
newGetTags ::
  -- | 'arn'
  Prelude.Text ->
  GetTags
newGetTags :: Text -> GetTags
newGetTags Text
pArn_ = GetTags' {$sel:arn:GetTags' :: Text
arn = Text
pArn_}

-- | The ARN of the resource group whose tags you want to retrieve.
getTags_arn :: Lens.Lens' GetTags Prelude.Text
getTags_arn :: Lens' GetTags Text
getTags_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTags' {Text
arn :: Text
$sel:arn:GetTags' :: GetTags -> Text
arn} -> Text
arn) (\s :: GetTags
s@GetTags' {} Text
a -> GetTags
s {$sel:arn:GetTags' :: Text
arn = Text
a} :: GetTags)

instance Core.AWSRequest GetTags where
  type AWSResponse GetTags = GetTagsResponse
  request :: (Service -> Service) -> GetTags -> Request GetTags
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetTags
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetTags)))
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 -> GetTagsResponse
GetTagsResponse'
            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 GetTags where
  hashWithSalt :: Int -> GetTags -> Int
hashWithSalt Int
_salt GetTags' {Text
arn :: Text
$sel:arn:GetTags' :: GetTags -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn

instance Prelude.NFData GetTags where
  rnf :: GetTags -> ()
rnf GetTags' {Text
arn :: Text
$sel:arn:GetTags' :: GetTags -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
arn

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

instance Data.ToPath GetTags where
  toPath :: GetTags -> ByteString
toPath GetTags' {Text
arn :: Text
$sel:arn:GetTags' :: GetTags -> 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 GetTags where
  toQuery :: GetTags -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

-- |
-- Create a value of 'GetTagsResponse' 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', 'getTagsResponse_arn' - The ARN of the tagged resource group.
--
-- 'tags', 'getTagsResponse_tags' - The tags associated with the specified resource group.
--
-- 'httpStatus', 'getTagsResponse_httpStatus' - The response's http status code.
newGetTagsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetTagsResponse
newGetTagsResponse :: Int -> GetTagsResponse
newGetTagsResponse Int
pHttpStatus_ =
  GetTagsResponse'
    { $sel:arn:GetTagsResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetTagsResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetTagsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | The tags associated with the specified resource group.
getTagsResponse_tags :: Lens.Lens' GetTagsResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getTagsResponse_tags :: Lens' GetTagsResponse (Maybe (HashMap Text Text))
getTagsResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTagsResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GetTagsResponse' :: GetTagsResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GetTagsResponse
s@GetTagsResponse' {} Maybe (HashMap Text Text)
a -> GetTagsResponse
s {$sel:tags:GetTagsResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: GetTagsResponse) 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.
getTagsResponse_httpStatus :: Lens.Lens' GetTagsResponse Prelude.Int
getTagsResponse_httpStatus :: Lens' GetTagsResponse Int
getTagsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTagsResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetTagsResponse' :: GetTagsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetTagsResponse
s@GetTagsResponse' {} Int
a -> GetTagsResponse
s {$sel:httpStatus:GetTagsResponse' :: Int
httpStatus = Int
a} :: GetTagsResponse)

instance Prelude.NFData GetTagsResponse where
  rnf :: GetTagsResponse -> ()
rnf GetTagsResponse' {Int
Maybe Text
Maybe (HashMap Text Text)
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
arn :: Maybe Text
$sel:httpStatus:GetTagsResponse' :: GetTagsResponse -> Int
$sel:tags:GetTagsResponse' :: GetTagsResponse -> Maybe (HashMap Text Text)
$sel:arn:GetTagsResponse' :: GetTagsResponse -> 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