{-# 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.KMS.ListResourceTags
-- 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 all tags on the specified KMS key.
--
-- For general information about tags, including the format and syntax, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services resources>
-- in the /Amazon Web Services General Reference/. For information about
-- using tags in KMS, see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/tagging-keys.html Tagging keys>.
--
-- __Cross-account use__: No. You cannot perform this operation on a KMS
-- key in a different Amazon Web Services account.
--
-- __Required permissions__:
-- <https://docs.aws.amazon.com/kms/latest/developerguide/kms-api-permissions-reference.html kms:ListResourceTags>
-- (key policy)
--
-- __Related operations:__
--
-- -   CreateKey
--
-- -   ReplicateKey
--
-- -   TagResource
--
-- -   UntagResource
--
-- This operation returns paginated results.
module Amazonka.KMS.ListResourceTags
  ( -- * Creating a Request
    ListResourceTags (..),
    newListResourceTags,

    -- * Request Lenses
    listResourceTags_limit,
    listResourceTags_marker,
    listResourceTags_keyId,

    -- * Destructuring the Response
    ListResourceTagsResponse (..),
    newListResourceTagsResponse,

    -- * Response Lenses
    listResourceTagsResponse_nextMarker,
    listResourceTagsResponse_tags,
    listResourceTagsResponse_truncated,
    listResourceTagsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.KMS.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListResourceTags' smart constructor.
data ListResourceTags = ListResourceTags'
  { -- | Use this parameter to specify the maximum number of items to return.
    -- When this value is present, KMS does not return more than the specified
    -- number of items, but it might return fewer.
    --
    -- This value is optional. If you include a value, it must be between 1 and
    -- 50, inclusive. If you do not include a value, it defaults to 50.
    ListResourceTags -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | Use this parameter in a subsequent request after you receive a response
    -- with truncated results. Set it to the value of @NextMarker@ from the
    -- truncated response you just received.
    --
    -- Do not attempt to construct this value. Use only the value of
    -- @NextMarker@ from the truncated response you just received.
    ListResourceTags -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | Gets tags on the specified KMS key.
    --
    -- Specify the key ID or key ARN of the KMS key.
    --
    -- For example:
    --
    -- -   Key ID: @1234abcd-12ab-34cd-56ef-1234567890ab@
    --
    -- -   Key ARN:
    --     @arn:aws:kms:us-east-2:111122223333:key\/1234abcd-12ab-34cd-56ef-1234567890ab@
    --
    -- To get the key ID and key ARN for a KMS key, use ListKeys or
    -- DescribeKey.
    ListResourceTags -> Text
keyId :: Prelude.Text
  }
  deriving (ListResourceTags -> ListResourceTags -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResourceTags -> ListResourceTags -> Bool
$c/= :: ListResourceTags -> ListResourceTags -> Bool
== :: ListResourceTags -> ListResourceTags -> Bool
$c== :: ListResourceTags -> ListResourceTags -> Bool
Prelude.Eq, ReadPrec [ListResourceTags]
ReadPrec ListResourceTags
Int -> ReadS ListResourceTags
ReadS [ListResourceTags]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResourceTags]
$creadListPrec :: ReadPrec [ListResourceTags]
readPrec :: ReadPrec ListResourceTags
$creadPrec :: ReadPrec ListResourceTags
readList :: ReadS [ListResourceTags]
$creadList :: ReadS [ListResourceTags]
readsPrec :: Int -> ReadS ListResourceTags
$creadsPrec :: Int -> ReadS ListResourceTags
Prelude.Read, Int -> ListResourceTags -> ShowS
[ListResourceTags] -> ShowS
ListResourceTags -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResourceTags] -> ShowS
$cshowList :: [ListResourceTags] -> ShowS
show :: ListResourceTags -> String
$cshow :: ListResourceTags -> String
showsPrec :: Int -> ListResourceTags -> ShowS
$cshowsPrec :: Int -> ListResourceTags -> ShowS
Prelude.Show, forall x. Rep ListResourceTags x -> ListResourceTags
forall x. ListResourceTags -> Rep ListResourceTags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListResourceTags x -> ListResourceTags
$cfrom :: forall x. ListResourceTags -> Rep ListResourceTags x
Prelude.Generic)

-- |
-- Create a value of 'ListResourceTags' 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', 'listResourceTags_limit' - Use this parameter to specify the maximum number of items to return.
-- When this value is present, KMS does not return more than the specified
-- number of items, but it might return fewer.
--
-- This value is optional. If you include a value, it must be between 1 and
-- 50, inclusive. If you do not include a value, it defaults to 50.
--
-- 'marker', 'listResourceTags_marker' - Use this parameter in a subsequent request after you receive a response
-- with truncated results. Set it to the value of @NextMarker@ from the
-- truncated response you just received.
--
-- Do not attempt to construct this value. Use only the value of
-- @NextMarker@ from the truncated response you just received.
--
-- 'keyId', 'listResourceTags_keyId' - Gets tags on the specified KMS key.
--
-- Specify the key ID or key ARN of the KMS key.
--
-- For example:
--
-- -   Key ID: @1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- -   Key ARN:
--     @arn:aws:kms:us-east-2:111122223333:key\/1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- To get the key ID and key ARN for a KMS key, use ListKeys or
-- DescribeKey.
newListResourceTags ::
  -- | 'keyId'
  Prelude.Text ->
  ListResourceTags
newListResourceTags :: Text -> ListResourceTags
newListResourceTags Text
pKeyId_ =
  ListResourceTags'
    { $sel:limit:ListResourceTags' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:ListResourceTags' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:keyId:ListResourceTags' :: Text
keyId = Text
pKeyId_
    }

-- | Use this parameter to specify the maximum number of items to return.
-- When this value is present, KMS does not return more than the specified
-- number of items, but it might return fewer.
--
-- This value is optional. If you include a value, it must be between 1 and
-- 50, inclusive. If you do not include a value, it defaults to 50.
listResourceTags_limit :: Lens.Lens' ListResourceTags (Prelude.Maybe Prelude.Natural)
listResourceTags_limit :: Lens' ListResourceTags (Maybe Natural)
listResourceTags_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceTags' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListResourceTags' :: ListResourceTags -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListResourceTags
s@ListResourceTags' {} Maybe Natural
a -> ListResourceTags
s {$sel:limit:ListResourceTags' :: Maybe Natural
limit = Maybe Natural
a} :: ListResourceTags)

-- | Use this parameter in a subsequent request after you receive a response
-- with truncated results. Set it to the value of @NextMarker@ from the
-- truncated response you just received.
--
-- Do not attempt to construct this value. Use only the value of
-- @NextMarker@ from the truncated response you just received.
listResourceTags_marker :: Lens.Lens' ListResourceTags (Prelude.Maybe Prelude.Text)
listResourceTags_marker :: Lens' ListResourceTags (Maybe Text)
listResourceTags_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceTags' {Maybe Text
marker :: Maybe Text
$sel:marker:ListResourceTags' :: ListResourceTags -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListResourceTags
s@ListResourceTags' {} Maybe Text
a -> ListResourceTags
s {$sel:marker:ListResourceTags' :: Maybe Text
marker = Maybe Text
a} :: ListResourceTags)

-- | Gets tags on the specified KMS key.
--
-- Specify the key ID or key ARN of the KMS key.
--
-- For example:
--
-- -   Key ID: @1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- -   Key ARN:
--     @arn:aws:kms:us-east-2:111122223333:key\/1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- To get the key ID and key ARN for a KMS key, use ListKeys or
-- DescribeKey.
listResourceTags_keyId :: Lens.Lens' ListResourceTags Prelude.Text
listResourceTags_keyId :: Lens' ListResourceTags Text
listResourceTags_keyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceTags' {Text
keyId :: Text
$sel:keyId:ListResourceTags' :: ListResourceTags -> Text
keyId} -> Text
keyId) (\s :: ListResourceTags
s@ListResourceTags' {} Text
a -> ListResourceTags
s {$sel:keyId:ListResourceTags' :: Text
keyId = Text
a} :: ListResourceTags)

instance Core.AWSPager ListResourceTags where
  page :: ListResourceTags
-> AWSResponse ListResourceTags -> Maybe ListResourceTags
page ListResourceTags
rq AWSResponse ListResourceTags
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListResourceTags
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourceTagsResponse (Maybe Bool)
listResourceTagsResponse_truncated
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. Maybe a -> Bool
Prelude.isNothing
        ( AWSResponse ListResourceTags
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourceTagsResponse (Maybe Text)
listResourceTagsResponse_nextMarker
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListResourceTags
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListResourceTags (Maybe Text)
listResourceTags_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListResourceTags
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourceTagsResponse (Maybe Text)
listResourceTagsResponse_nextMarker
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListResourceTags where
  type
    AWSResponse ListResourceTags =
      ListResourceTagsResponse
  request :: (Service -> Service)
-> ListResourceTags -> Request ListResourceTags
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListResourceTags
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListResourceTags)))
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 [Tag] -> Maybe Bool -> Int -> ListResourceTagsResponse
ListResourceTagsResponse'
            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
"NextMarker")
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Truncated")
            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 ListResourceTags where
  hashWithSalt :: Int -> ListResourceTags -> Int
hashWithSalt Int
_salt ListResourceTags' {Maybe Natural
Maybe Text
Text
keyId :: Text
marker :: Maybe Text
limit :: Maybe Natural
$sel:keyId:ListResourceTags' :: ListResourceTags -> Text
$sel:marker:ListResourceTags' :: ListResourceTags -> Maybe Text
$sel:limit:ListResourceTags' :: ListResourceTags -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
keyId

instance Prelude.NFData ListResourceTags where
  rnf :: ListResourceTags -> ()
rnf ListResourceTags' {Maybe Natural
Maybe Text
Text
keyId :: Text
marker :: Maybe Text
limit :: Maybe Natural
$sel:keyId:ListResourceTags' :: ListResourceTags -> Text
$sel:marker:ListResourceTags' :: ListResourceTags -> Maybe Text
$sel:limit:ListResourceTags' :: ListResourceTags -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
keyId

instance Data.ToHeaders ListResourceTags where
  toHeaders :: ListResourceTags -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"TrentService.ListResourceTags" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListResourceTags where
  toJSON :: ListResourceTags -> Value
toJSON ListResourceTags' {Maybe Natural
Maybe Text
Text
keyId :: Text
marker :: Maybe Text
limit :: Maybe Natural
$sel:keyId:ListResourceTags' :: ListResourceTags -> Text
$sel:marker:ListResourceTags' :: ListResourceTags -> Maybe Text
$sel:limit:ListResourceTags' :: ListResourceTags -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Limit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
limit,
            (Key
"Marker" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
marker,
            forall a. a -> Maybe a
Prelude.Just (Key
"KeyId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
keyId)
          ]
      )

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

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

-- | /See:/ 'newListResourceTagsResponse' smart constructor.
data ListResourceTagsResponse = ListResourceTagsResponse'
  { -- | When @Truncated@ is true, this element is present and contains the value
    -- to use for the @Marker@ parameter in a subsequent request.
    --
    -- Do not assume or infer any information from this value.
    ListResourceTagsResponse -> Maybe Text
nextMarker :: Prelude.Maybe Prelude.Text,
    -- | A list of tags. Each tag consists of a tag key and a tag value.
    --
    -- Tagging or untagging a KMS key can allow or deny permission to the KMS
    -- key. For details, see
    -- <https://docs.aws.amazon.com/kms/latest/developerguide/abac.html ABAC for KMS>
    -- in the /Key Management Service Developer Guide/.
    ListResourceTagsResponse -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | A flag that indicates whether there are more items in the list. When
    -- this value is true, the list in this response is truncated. To get more
    -- items, pass the value of the @NextMarker@ element in thisresponse to the
    -- @Marker@ parameter in a subsequent request.
    ListResourceTagsResponse -> Maybe Bool
truncated :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    ListResourceTagsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListResourceTagsResponse -> ListResourceTagsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResourceTagsResponse -> ListResourceTagsResponse -> Bool
$c/= :: ListResourceTagsResponse -> ListResourceTagsResponse -> Bool
== :: ListResourceTagsResponse -> ListResourceTagsResponse -> Bool
$c== :: ListResourceTagsResponse -> ListResourceTagsResponse -> Bool
Prelude.Eq, ReadPrec [ListResourceTagsResponse]
ReadPrec ListResourceTagsResponse
Int -> ReadS ListResourceTagsResponse
ReadS [ListResourceTagsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResourceTagsResponse]
$creadListPrec :: ReadPrec [ListResourceTagsResponse]
readPrec :: ReadPrec ListResourceTagsResponse
$creadPrec :: ReadPrec ListResourceTagsResponse
readList :: ReadS [ListResourceTagsResponse]
$creadList :: ReadS [ListResourceTagsResponse]
readsPrec :: Int -> ReadS ListResourceTagsResponse
$creadsPrec :: Int -> ReadS ListResourceTagsResponse
Prelude.Read, Int -> ListResourceTagsResponse -> ShowS
[ListResourceTagsResponse] -> ShowS
ListResourceTagsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResourceTagsResponse] -> ShowS
$cshowList :: [ListResourceTagsResponse] -> ShowS
show :: ListResourceTagsResponse -> String
$cshow :: ListResourceTagsResponse -> String
showsPrec :: Int -> ListResourceTagsResponse -> ShowS
$cshowsPrec :: Int -> ListResourceTagsResponse -> ShowS
Prelude.Show, forall x.
Rep ListResourceTagsResponse x -> ListResourceTagsResponse
forall x.
ListResourceTagsResponse -> Rep ListResourceTagsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListResourceTagsResponse x -> ListResourceTagsResponse
$cfrom :: forall x.
ListResourceTagsResponse -> Rep ListResourceTagsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListResourceTagsResponse' 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:
--
-- 'nextMarker', 'listResourceTagsResponse_nextMarker' - When @Truncated@ is true, this element is present and contains the value
-- to use for the @Marker@ parameter in a subsequent request.
--
-- Do not assume or infer any information from this value.
--
-- 'tags', 'listResourceTagsResponse_tags' - A list of tags. Each tag consists of a tag key and a tag value.
--
-- Tagging or untagging a KMS key can allow or deny permission to the KMS
-- key. For details, see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/abac.html ABAC for KMS>
-- in the /Key Management Service Developer Guide/.
--
-- 'truncated', 'listResourceTagsResponse_truncated' - A flag that indicates whether there are more items in the list. When
-- this value is true, the list in this response is truncated. To get more
-- items, pass the value of the @NextMarker@ element in thisresponse to the
-- @Marker@ parameter in a subsequent request.
--
-- 'httpStatus', 'listResourceTagsResponse_httpStatus' - The response's http status code.
newListResourceTagsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListResourceTagsResponse
newListResourceTagsResponse :: Int -> ListResourceTagsResponse
newListResourceTagsResponse Int
pHttpStatus_ =
  ListResourceTagsResponse'
    { $sel:nextMarker:ListResourceTagsResponse' :: Maybe Text
nextMarker =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ListResourceTagsResponse' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:truncated:ListResourceTagsResponse' :: Maybe Bool
truncated = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListResourceTagsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | When @Truncated@ is true, this element is present and contains the value
-- to use for the @Marker@ parameter in a subsequent request.
--
-- Do not assume or infer any information from this value.
listResourceTagsResponse_nextMarker :: Lens.Lens' ListResourceTagsResponse (Prelude.Maybe Prelude.Text)
listResourceTagsResponse_nextMarker :: Lens' ListResourceTagsResponse (Maybe Text)
listResourceTagsResponse_nextMarker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceTagsResponse' {Maybe Text
nextMarker :: Maybe Text
$sel:nextMarker:ListResourceTagsResponse' :: ListResourceTagsResponse -> Maybe Text
nextMarker} -> Maybe Text
nextMarker) (\s :: ListResourceTagsResponse
s@ListResourceTagsResponse' {} Maybe Text
a -> ListResourceTagsResponse
s {$sel:nextMarker:ListResourceTagsResponse' :: Maybe Text
nextMarker = Maybe Text
a} :: ListResourceTagsResponse)

-- | A list of tags. Each tag consists of a tag key and a tag value.
--
-- Tagging or untagging a KMS key can allow or deny permission to the KMS
-- key. For details, see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/abac.html ABAC for KMS>
-- in the /Key Management Service Developer Guide/.
listResourceTagsResponse_tags :: Lens.Lens' ListResourceTagsResponse (Prelude.Maybe [Tag])
listResourceTagsResponse_tags :: Lens' ListResourceTagsResponse (Maybe [Tag])
listResourceTagsResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceTagsResponse' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:ListResourceTagsResponse' :: ListResourceTagsResponse -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: ListResourceTagsResponse
s@ListResourceTagsResponse' {} Maybe [Tag]
a -> ListResourceTagsResponse
s {$sel:tags:ListResourceTagsResponse' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: ListResourceTagsResponse) 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

-- | A flag that indicates whether there are more items in the list. When
-- this value is true, the list in this response is truncated. To get more
-- items, pass the value of the @NextMarker@ element in thisresponse to the
-- @Marker@ parameter in a subsequent request.
listResourceTagsResponse_truncated :: Lens.Lens' ListResourceTagsResponse (Prelude.Maybe Prelude.Bool)
listResourceTagsResponse_truncated :: Lens' ListResourceTagsResponse (Maybe Bool)
listResourceTagsResponse_truncated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceTagsResponse' {Maybe Bool
truncated :: Maybe Bool
$sel:truncated:ListResourceTagsResponse' :: ListResourceTagsResponse -> Maybe Bool
truncated} -> Maybe Bool
truncated) (\s :: ListResourceTagsResponse
s@ListResourceTagsResponse' {} Maybe Bool
a -> ListResourceTagsResponse
s {$sel:truncated:ListResourceTagsResponse' :: Maybe Bool
truncated = Maybe Bool
a} :: ListResourceTagsResponse)

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

instance Prelude.NFData ListResourceTagsResponse where
  rnf :: ListResourceTagsResponse -> ()
rnf ListResourceTagsResponse' {Int
Maybe Bool
Maybe [Tag]
Maybe Text
httpStatus :: Int
truncated :: Maybe Bool
tags :: Maybe [Tag]
nextMarker :: Maybe Text
$sel:httpStatus:ListResourceTagsResponse' :: ListResourceTagsResponse -> Int
$sel:truncated:ListResourceTagsResponse' :: ListResourceTagsResponse -> Maybe Bool
$sel:tags:ListResourceTagsResponse' :: ListResourceTagsResponse -> Maybe [Tag]
$sel:nextMarker:ListResourceTagsResponse' :: ListResourceTagsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextMarker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
truncated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus