{-# 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.CloudHSMV2.ListTags
-- 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 a list of tags for the specified AWS CloudHSM cluster.
--
-- This is a paginated operation, which means that each response might
-- contain only a subset of all the tags. When the response contains only a
-- subset of tags, it includes a @NextToken@ value. Use this value in a
-- subsequent @ListTags@ request to get more tags. When you receive a
-- response with no @NextToken@ (or an empty or null value), that means
-- there are no more tags to get.
--
-- This operation returns paginated results.
module Amazonka.CloudHSMV2.ListTags
  ( -- * Creating a Request
    ListTags (..),
    newListTags,

    -- * Request Lenses
    listTags_maxResults,
    listTags_nextToken,
    listTags_resourceId,

    -- * Destructuring the Response
    ListTagsResponse (..),
    newListTagsResponse,

    -- * Response Lenses
    listTagsResponse_nextToken,
    listTagsResponse_httpStatus,
    listTagsResponse_tagList,
  )
where

import Amazonka.CloudHSMV2.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

-- | /See:/ 'newListTags' smart constructor.
data ListTags = ListTags'
  { -- | The maximum number of tags to return in the response. When there are
    -- more tags than the number you specify, the response contains a
    -- @NextToken@ value.
    ListTags -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The @NextToken@ value that you received in the previous response. Use
    -- this value to get more tags.
    ListTags -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The cluster identifier (ID) for the cluster whose tags you are getting.
    -- To find the cluster ID, use DescribeClusters.
    ListTags -> Text
resourceId :: Prelude.Text
  }
  deriving (ListTags -> ListTags -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTags -> ListTags -> Bool
$c/= :: ListTags -> ListTags -> Bool
== :: ListTags -> ListTags -> Bool
$c== :: ListTags -> ListTags -> Bool
Prelude.Eq, ReadPrec [ListTags]
ReadPrec ListTags
Int -> ReadS ListTags
ReadS [ListTags]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTags]
$creadListPrec :: ReadPrec [ListTags]
readPrec :: ReadPrec ListTags
$creadPrec :: ReadPrec ListTags
readList :: ReadS [ListTags]
$creadList :: ReadS [ListTags]
readsPrec :: Int -> ReadS ListTags
$creadsPrec :: Int -> ReadS ListTags
Prelude.Read, Int -> ListTags -> ShowS
[ListTags] -> ShowS
ListTags -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTags] -> ShowS
$cshowList :: [ListTags] -> ShowS
show :: ListTags -> String
$cshow :: ListTags -> String
showsPrec :: Int -> ListTags -> ShowS
$cshowsPrec :: Int -> ListTags -> ShowS
Prelude.Show, forall x. Rep ListTags x -> ListTags
forall x. ListTags -> Rep ListTags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTags x -> ListTags
$cfrom :: forall x. ListTags -> Rep ListTags x
Prelude.Generic)

-- |
-- Create a value of 'ListTags' 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:
--
-- 'maxResults', 'listTags_maxResults' - The maximum number of tags to return in the response. When there are
-- more tags than the number you specify, the response contains a
-- @NextToken@ value.
--
-- 'nextToken', 'listTags_nextToken' - The @NextToken@ value that you received in the previous response. Use
-- this value to get more tags.
--
-- 'resourceId', 'listTags_resourceId' - The cluster identifier (ID) for the cluster whose tags you are getting.
-- To find the cluster ID, use DescribeClusters.
newListTags ::
  -- | 'resourceId'
  Prelude.Text ->
  ListTags
newListTags :: Text -> ListTags
newListTags Text
pResourceId_ =
  ListTags'
    { $sel:maxResults:ListTags' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListTags' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceId:ListTags' :: Text
resourceId = Text
pResourceId_
    }

-- | The maximum number of tags to return in the response. When there are
-- more tags than the number you specify, the response contains a
-- @NextToken@ value.
listTags_maxResults :: Lens.Lens' ListTags (Prelude.Maybe Prelude.Natural)
listTags_maxResults :: Lens' ListTags (Maybe Natural)
listTags_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTags' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListTags' :: ListTags -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListTags
s@ListTags' {} Maybe Natural
a -> ListTags
s {$sel:maxResults:ListTags' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListTags)

-- | The @NextToken@ value that you received in the previous response. Use
-- this value to get more tags.
listTags_nextToken :: Lens.Lens' ListTags (Prelude.Maybe Prelude.Text)
listTags_nextToken :: Lens' ListTags (Maybe Text)
listTags_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTags' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTags' :: ListTags -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTags
s@ListTags' {} Maybe Text
a -> ListTags
s {$sel:nextToken:ListTags' :: Maybe Text
nextToken = Maybe Text
a} :: ListTags)

-- | The cluster identifier (ID) for the cluster whose tags you are getting.
-- To find the cluster ID, use DescribeClusters.
listTags_resourceId :: Lens.Lens' ListTags Prelude.Text
listTags_resourceId :: Lens' ListTags Text
listTags_resourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTags' {Text
resourceId :: Text
$sel:resourceId:ListTags' :: ListTags -> Text
resourceId} -> Text
resourceId) (\s :: ListTags
s@ListTags' {} Text
a -> ListTags
s {$sel:resourceId:ListTags' :: Text
resourceId = Text
a} :: ListTags)

instance Core.AWSPager ListTags where
  page :: ListTags -> AWSResponse ListTags -> Maybe ListTags
page ListTags
rq AWSResponse ListTags
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListTags
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTagsResponse (Maybe Text)
listTagsResponse_nextToken
            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. AWSTruncated a => a -> Bool
Core.stop (AWSResponse ListTags
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListTagsResponse [Tag]
listTagsResponse_tagList) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListTags
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListTags (Maybe Text)
listTags_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListTags
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTagsResponse (Maybe Text)
listTagsResponse_nextToken
          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 ListTags where
  type AWSResponse ListTags = ListTagsResponse
  request :: (Service -> Service) -> ListTags -> Request ListTags
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 ListTags
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListTags)))
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 -> Int -> [Tag] -> ListTagsResponse
ListTagsResponse'
            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
"NextToken")
            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))
            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
"TagList" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ListTags where
  hashWithSalt :: Int -> ListTags -> Int
hashWithSalt Int
_salt ListTags' {Maybe Natural
Maybe Text
Text
resourceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceId:ListTags' :: ListTags -> Text
$sel:nextToken:ListTags' :: ListTags -> Maybe Text
$sel:maxResults:ListTags' :: ListTags -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceId

instance Prelude.NFData ListTags where
  rnf :: ListTags -> ()
rnf ListTags' {Maybe Natural
Maybe Text
Text
resourceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceId:ListTags' :: ListTags -> Text
$sel:nextToken:ListTags' :: ListTags -> Maybe Text
$sel:maxResults:ListTags' :: ListTags -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceId

instance Data.ToHeaders ListTags where
  toHeaders :: ListTags -> 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
"BaldrApiService.ListTags" :: 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 ListTags where
  toJSON :: ListTags -> Value
toJSON ListTags' {Maybe Natural
Maybe Text
Text
resourceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceId:ListTags' :: ListTags -> Text
$sel:nextToken:ListTags' :: ListTags -> Maybe Text
$sel:maxResults:ListTags' :: ListTags -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaxResults" 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
maxResults,
            (Key
"NextToken" 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
nextToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"ResourceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceId)
          ]
      )

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

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

-- | /See:/ 'newListTagsResponse' smart constructor.
data ListTagsResponse = ListTagsResponse'
  { -- | An opaque string that indicates that the response contains only a subset
    -- of tags. Use this value in a subsequent @ListTags@ request to get more
    -- tags.
    ListTagsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListTagsResponse -> Int
httpStatus :: Prelude.Int,
    -- | A list of tags.
    ListTagsResponse -> [Tag]
tagList :: [Tag]
  }
  deriving (ListTagsResponse -> ListTagsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTagsResponse -> ListTagsResponse -> Bool
$c/= :: ListTagsResponse -> ListTagsResponse -> Bool
== :: ListTagsResponse -> ListTagsResponse -> Bool
$c== :: ListTagsResponse -> ListTagsResponse -> Bool
Prelude.Eq, ReadPrec [ListTagsResponse]
ReadPrec ListTagsResponse
Int -> ReadS ListTagsResponse
ReadS [ListTagsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTagsResponse]
$creadListPrec :: ReadPrec [ListTagsResponse]
readPrec :: ReadPrec ListTagsResponse
$creadPrec :: ReadPrec ListTagsResponse
readList :: ReadS [ListTagsResponse]
$creadList :: ReadS [ListTagsResponse]
readsPrec :: Int -> ReadS ListTagsResponse
$creadsPrec :: Int -> ReadS ListTagsResponse
Prelude.Read, Int -> ListTagsResponse -> ShowS
[ListTagsResponse] -> ShowS
ListTagsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTagsResponse] -> ShowS
$cshowList :: [ListTagsResponse] -> ShowS
show :: ListTagsResponse -> String
$cshow :: ListTagsResponse -> String
showsPrec :: Int -> ListTagsResponse -> ShowS
$cshowsPrec :: Int -> ListTagsResponse -> ShowS
Prelude.Show, forall x. Rep ListTagsResponse x -> ListTagsResponse
forall x. ListTagsResponse -> Rep ListTagsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTagsResponse x -> ListTagsResponse
$cfrom :: forall x. ListTagsResponse -> Rep ListTagsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListTagsResponse' 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:
--
-- 'nextToken', 'listTagsResponse_nextToken' - An opaque string that indicates that the response contains only a subset
-- of tags. Use this value in a subsequent @ListTags@ request to get more
-- tags.
--
-- 'httpStatus', 'listTagsResponse_httpStatus' - The response's http status code.
--
-- 'tagList', 'listTagsResponse_tagList' - A list of tags.
newListTagsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListTagsResponse
newListTagsResponse :: Int -> ListTagsResponse
newListTagsResponse Int
pHttpStatus_ =
  ListTagsResponse'
    { $sel:nextToken:ListTagsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListTagsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:tagList:ListTagsResponse' :: [Tag]
tagList = forall a. Monoid a => a
Prelude.mempty
    }

-- | An opaque string that indicates that the response contains only a subset
-- of tags. Use this value in a subsequent @ListTags@ request to get more
-- tags.
listTagsResponse_nextToken :: Lens.Lens' ListTagsResponse (Prelude.Maybe Prelude.Text)
listTagsResponse_nextToken :: Lens' ListTagsResponse (Maybe Text)
listTagsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTagsResponse' :: ListTagsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTagsResponse
s@ListTagsResponse' {} Maybe Text
a -> ListTagsResponse
s {$sel:nextToken:ListTagsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListTagsResponse)

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

-- | A list of tags.
listTagsResponse_tagList :: Lens.Lens' ListTagsResponse [Tag]
listTagsResponse_tagList :: Lens' ListTagsResponse [Tag]
listTagsResponse_tagList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsResponse' {[Tag]
tagList :: [Tag]
$sel:tagList:ListTagsResponse' :: ListTagsResponse -> [Tag]
tagList} -> [Tag]
tagList) (\s :: ListTagsResponse
s@ListTagsResponse' {} [Tag]
a -> ListTagsResponse
s {$sel:tagList:ListTagsResponse' :: [Tag]
tagList = [Tag]
a} :: ListTagsResponse) 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 Prelude.NFData ListTagsResponse where
  rnf :: ListTagsResponse -> ()
rnf ListTagsResponse' {Int
[Tag]
Maybe Text
tagList :: [Tag]
httpStatus :: Int
nextToken :: Maybe Text
$sel:tagList:ListTagsResponse' :: ListTagsResponse -> [Tag]
$sel:httpStatus:ListTagsResponse' :: ListTagsResponse -> Int
$sel:nextToken:ListTagsResponse' :: ListTagsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Tag]
tagList