{-# 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.Backup.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)
--
-- Returns a list of key-value pairs assigned to a target recovery point,
-- backup plan, or backup vault.
--
-- @ListTags@ only works for resource types that support full Backup
-- management of their backups. Those resource types are listed in the
-- \"Full Backup management\" section of the
-- <https://docs.aws.amazon.com/aws-backup/latest/devguide/whatisbackup.html#features-by-resource Feature availability by resource>
-- table.
module Amazonka.Backup.ListTags
  ( -- * Creating a Request
    ListTags (..),
    newListTags,

    -- * Request Lenses
    listTags_maxResults,
    listTags_nextToken,
    listTags_resourceArn,

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

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

import Amazonka.Backup.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 items to be returned.
    ListTags -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The next item following a partial list of returned items. For example,
    -- if a request is made to return @maxResults@ number of items, @NextToken@
    -- allows you to return more items in your list starting at the location
    -- pointed to by the next token.
    ListTags -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An Amazon Resource Name (ARN) that uniquely identifies a resource. The
    -- format of the ARN depends on the type of resource. Valid targets for
    -- @ListTags@ are recovery points, backup plans, and backup vaults.
    ListTags -> Text
resourceArn :: 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 items to be returned.
--
-- 'nextToken', 'listTags_nextToken' - The next item following a partial list of returned items. For example,
-- if a request is made to return @maxResults@ number of items, @NextToken@
-- allows you to return more items in your list starting at the location
-- pointed to by the next token.
--
-- 'resourceArn', 'listTags_resourceArn' - An Amazon Resource Name (ARN) that uniquely identifies a resource. The
-- format of the ARN depends on the type of resource. Valid targets for
-- @ListTags@ are recovery points, backup plans, and backup vaults.
newListTags ::
  -- | 'resourceArn'
  Prelude.Text ->
  ListTags
newListTags :: Text -> ListTags
newListTags Text
pResourceArn_ =
  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:resourceArn:ListTags' :: Text
resourceArn = Text
pResourceArn_
    }

-- | The maximum number of items to be returned.
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 next item following a partial list of returned items. For example,
-- if a request is made to return @maxResults@ number of items, @NextToken@
-- allows you to return more items in your list starting at the location
-- pointed to by the next token.
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)

-- | An Amazon Resource Name (ARN) that uniquely identifies a resource. The
-- format of the ARN depends on the type of resource. Valid targets for
-- @ListTags@ are recovery points, backup plans, and backup vaults.
listTags_resourceArn :: Lens.Lens' ListTags Prelude.Text
listTags_resourceArn :: Lens' ListTags Text
listTags_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTags' {Text
resourceArn :: Text
$sel:resourceArn:ListTags' :: ListTags -> Text
resourceArn} -> Text
resourceArn) (\s :: ListTags
s@ListTags' {} Text
a -> ListTags
s {$sel:resourceArn:ListTags' :: Text
resourceArn = Text
a} :: ListTags)

instance Core.AWSRequest ListTags where
  type AWSResponse ListTags = ListTagsResponse
  request :: (Service -> Service) -> ListTags -> Request ListTags
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 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
-> Maybe (Sensitive (HashMap Text Text)) -> Int -> 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.<*> (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 ListTags where
  hashWithSalt :: Int -> ListTags -> Int
hashWithSalt Int
_salt ListTags' {Maybe Natural
Maybe Text
Text
resourceArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceArn: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
resourceArn

instance Prelude.NFData ListTags where
  rnf :: ListTags -> ()
rnf ListTags' {Maybe Natural
Maybe Text
Text
resourceArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceArn: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
resourceArn

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
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

instance Data.ToQuery ListTags where
  toQuery :: ListTags -> QueryString
toQuery ListTags' {Maybe Natural
Maybe Text
Text
resourceArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceArn:ListTags' :: ListTags -> Text
$sel:nextToken:ListTags' :: ListTags -> Maybe Text
$sel:maxResults:ListTags' :: ListTags -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newListTagsResponse' smart constructor.
data ListTagsResponse = ListTagsResponse'
  { -- | The next item following a partial list of returned items. For example,
    -- if a request is made to return @maxResults@ number of items, @NextToken@
    -- allows you to return more items in your list starting at the location
    -- pointed to by the next token.
    ListTagsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | To help organize your resources, you can assign your own metadata to the
    -- resources you create. Each tag is a key-value pair.
    ListTagsResponse -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | The response's http status code.
    ListTagsResponse -> Int
httpStatus :: Prelude.Int
  }
  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, 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' - The next item following a partial list of returned items. For example,
-- if a request is made to return @maxResults@ number of items, @NextToken@
-- allows you to return more items in your list starting at the location
-- pointed to by the next token.
--
-- 'tags', 'listTagsResponse_tags' - To help organize your resources, you can assign your own metadata to the
-- resources you create. Each tag is a key-value pair.
--
-- 'httpStatus', 'listTagsResponse_httpStatus' - The response's http status code.
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:tags:ListTagsResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListTagsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The next item following a partial list of returned items. For example,
-- if a request is made to return @maxResults@ number of items, @NextToken@
-- allows you to return more items in your list starting at the location
-- pointed to by the next token.
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)

-- | To help organize your resources, you can assign your own metadata to the
-- resources you create. Each tag is a key-value pair.
listTagsResponse_tags :: Lens.Lens' ListTagsResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
listTagsResponse_tags :: Lens' ListTagsResponse (Maybe (HashMap Text Text))
listTagsResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsResponse' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:ListTagsResponse' :: ListTagsResponse -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: ListTagsResponse
s@ListTagsResponse' {} Maybe (Sensitive (HashMap Text Text))
a -> ListTagsResponse
s {$sel:tags:ListTagsResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: ListTagsResponse) 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 a. Iso' (Sensitive a) a
Data._Sensitive 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)

-- | 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)

instance Prelude.NFData ListTagsResponse where
  rnf :: ListTagsResponse -> ()
rnf ListTagsResponse' {Int
Maybe Text
Maybe (Sensitive (HashMap Text Text))
httpStatus :: Int
tags :: Maybe (Sensitive (HashMap Text Text))
nextToken :: Maybe Text
$sel:httpStatus:ListTagsResponse' :: ListTagsResponse -> Int
$sel:tags:ListTagsResponse' :: ListTagsResponse -> Maybe (Sensitive (HashMap Text Text))
$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 Maybe (Sensitive (HashMap Text Text))
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus