{-# 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.APIGateway.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)
--
-- Gets the Tags collection for a given resource.
module Amazonka.APIGateway.GetTags
  ( -- * Creating a Request
    GetTags (..),
    newGetTags,

    -- * Request Lenses
    getTags_limit,
    getTags_position,
    getTags_resourceArn,

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

    -- * Response Lenses
    getTagsResponse_tags,
    getTagsResponse_httpStatus,
  )
where

import Amazonka.APIGateway.Types
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

-- | Gets the Tags collection for a given resource.
--
-- /See:/ 'newGetTags' smart constructor.
data GetTags = GetTags'
  { -- | (Not currently supported) The maximum number of returned results per
    -- page. The default value is 25 and the maximum value is 500.
    GetTags -> Maybe Int
limit :: Prelude.Maybe Prelude.Int,
    -- | (Not currently supported) The current pagination position in the paged
    -- result set.
    GetTags -> Maybe Text
position :: Prelude.Maybe Prelude.Text,
    -- | The ARN of a resource that can be tagged.
    GetTags -> Text
resourceArn :: 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:
--
-- 'limit', 'getTags_limit' - (Not currently supported) The maximum number of returned results per
-- page. The default value is 25 and the maximum value is 500.
--
-- 'position', 'getTags_position' - (Not currently supported) The current pagination position in the paged
-- result set.
--
-- 'resourceArn', 'getTags_resourceArn' - The ARN of a resource that can be tagged.
newGetTags ::
  -- | 'resourceArn'
  Prelude.Text ->
  GetTags
newGetTags :: Text -> GetTags
newGetTags Text
pResourceArn_ =
  GetTags'
    { $sel:limit:GetTags' :: Maybe Int
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:position:GetTags' :: Maybe Text
position = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArn:GetTags' :: Text
resourceArn = Text
pResourceArn_
    }

-- | (Not currently supported) The maximum number of returned results per
-- page. The default value is 25 and the maximum value is 500.
getTags_limit :: Lens.Lens' GetTags (Prelude.Maybe Prelude.Int)
getTags_limit :: Lens' GetTags (Maybe Int)
getTags_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTags' {Maybe Int
limit :: Maybe Int
$sel:limit:GetTags' :: GetTags -> Maybe Int
limit} -> Maybe Int
limit) (\s :: GetTags
s@GetTags' {} Maybe Int
a -> GetTags
s {$sel:limit:GetTags' :: Maybe Int
limit = Maybe Int
a} :: GetTags)

-- | (Not currently supported) The current pagination position in the paged
-- result set.
getTags_position :: Lens.Lens' GetTags (Prelude.Maybe Prelude.Text)
getTags_position :: Lens' GetTags (Maybe Text)
getTags_position = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTags' {Maybe Text
position :: Maybe Text
$sel:position:GetTags' :: GetTags -> Maybe Text
position} -> Maybe Text
position) (\s :: GetTags
s@GetTags' {} Maybe Text
a -> GetTags
s {$sel:position:GetTags' :: Maybe Text
position = Maybe Text
a} :: GetTags)

-- | The ARN of a resource that can be tagged.
getTags_resourceArn :: Lens.Lens' GetTags Prelude.Text
getTags_resourceArn :: Lens' GetTags Text
getTags_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTags' {Text
resourceArn :: Text
$sel:resourceArn:GetTags' :: GetTags -> Text
resourceArn} -> Text
resourceArn) (\s :: GetTags
s@GetTags' {} Text
a -> GetTags
s {$sel:resourceArn:GetTags' :: Text
resourceArn = 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 (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
"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' {Maybe Int
Maybe Text
Text
resourceArn :: Text
position :: Maybe Text
limit :: Maybe Int
$sel:resourceArn:GetTags' :: GetTags -> Text
$sel:position:GetTags' :: GetTags -> Maybe Text
$sel:limit:GetTags' :: GetTags -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
position
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn

instance Prelude.NFData GetTags where
  rnf :: GetTags -> ()
rnf GetTags' {Maybe Int
Maybe Text
Text
resourceArn :: Text
position :: Maybe Text
limit :: Maybe Int
$sel:resourceArn:GetTags' :: GetTags -> Text
$sel:position:GetTags' :: GetTags -> Maybe Text
$sel:limit:GetTags' :: GetTags -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
position
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn

instance Data.ToHeaders GetTags where
  toHeaders :: GetTags -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Accept"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/json" :: Prelude.ByteString)
          ]
      )

instance Data.ToPath GetTags where
  toPath :: GetTags -> ByteString
toPath GetTags' {Maybe Int
Maybe Text
Text
resourceArn :: Text
position :: Maybe Text
limit :: Maybe Int
$sel:resourceArn:GetTags' :: GetTags -> Text
$sel:position:GetTags' :: GetTags -> Maybe Text
$sel:limit:GetTags' :: GetTags -> Maybe Int
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/tags/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
resourceArn]

instance Data.ToQuery GetTags where
  toQuery :: GetTags -> QueryString
toQuery GetTags' {Maybe Int
Maybe Text
Text
resourceArn :: Text
position :: Maybe Text
limit :: Maybe Int
$sel:resourceArn:GetTags' :: GetTags -> Text
$sel:position:GetTags' :: GetTags -> Maybe Text
$sel:limit:GetTags' :: GetTags -> Maybe Int
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"limit" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
limit, ByteString
"position" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
position]

-- | The collection of tags. Each tag element is associated with a given
-- resource.
--
-- /See:/ 'newGetTagsResponse' smart constructor.
data GetTagsResponse = GetTagsResponse'
  { -- | The collection of tags. Each tag element is associated with a given
    -- resource.
    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:
--
-- 'tags', 'getTagsResponse_tags' - The collection of tags. Each tag element is associated with a given
-- resource.
--
-- 'httpStatus', 'getTagsResponse_httpStatus' - The response's http status code.
newGetTagsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetTagsResponse
newGetTagsResponse :: Int -> GetTagsResponse
newGetTagsResponse Int
pHttpStatus_ =
  GetTagsResponse'
    { $sel:tags:GetTagsResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetTagsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The collection of tags. Each tag element is associated with a given
-- resource.
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 (HashMap Text Text)
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
$sel:httpStatus:GetTagsResponse' :: GetTagsResponse -> Int
$sel:tags:GetTagsResponse' :: GetTagsResponse -> Maybe (HashMap Text Text)
..} =
    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