{-# 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.CertificateManager.ListTagsForCertificate
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the tags that have been applied to the ACM certificate. Use the
-- certificate\'s Amazon Resource Name (ARN) to specify the certificate. To
-- add a tag to an ACM certificate, use the AddTagsToCertificate action. To
-- delete a tag, use the RemoveTagsFromCertificate action.
module Amazonka.CertificateManager.ListTagsForCertificate
  ( -- * Creating a Request
    ListTagsForCertificate (..),
    newListTagsForCertificate,

    -- * Request Lenses
    listTagsForCertificate_certificateArn,

    -- * Destructuring the Response
    ListTagsForCertificateResponse (..),
    newListTagsForCertificateResponse,

    -- * Response Lenses
    listTagsForCertificateResponse_tags,
    listTagsForCertificateResponse_httpStatus,
  )
where

import Amazonka.CertificateManager.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:/ 'newListTagsForCertificate' smart constructor.
data ListTagsForCertificate = ListTagsForCertificate'
  { -- | String that contains the ARN of the ACM certificate for which you want
    -- to list the tags. This must have the following form:
    --
    -- @arn:aws:acm:region:123456789012:certificate\/12345678-1234-1234-1234-123456789012@
    --
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
    ListTagsForCertificate -> Text
certificateArn :: Prelude.Text
  }
  deriving (ListTagsForCertificate -> ListTagsForCertificate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTagsForCertificate -> ListTagsForCertificate -> Bool
$c/= :: ListTagsForCertificate -> ListTagsForCertificate -> Bool
== :: ListTagsForCertificate -> ListTagsForCertificate -> Bool
$c== :: ListTagsForCertificate -> ListTagsForCertificate -> Bool
Prelude.Eq, ReadPrec [ListTagsForCertificate]
ReadPrec ListTagsForCertificate
Int -> ReadS ListTagsForCertificate
ReadS [ListTagsForCertificate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTagsForCertificate]
$creadListPrec :: ReadPrec [ListTagsForCertificate]
readPrec :: ReadPrec ListTagsForCertificate
$creadPrec :: ReadPrec ListTagsForCertificate
readList :: ReadS [ListTagsForCertificate]
$creadList :: ReadS [ListTagsForCertificate]
readsPrec :: Int -> ReadS ListTagsForCertificate
$creadsPrec :: Int -> ReadS ListTagsForCertificate
Prelude.Read, Int -> ListTagsForCertificate -> ShowS
[ListTagsForCertificate] -> ShowS
ListTagsForCertificate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTagsForCertificate] -> ShowS
$cshowList :: [ListTagsForCertificate] -> ShowS
show :: ListTagsForCertificate -> String
$cshow :: ListTagsForCertificate -> String
showsPrec :: Int -> ListTagsForCertificate -> ShowS
$cshowsPrec :: Int -> ListTagsForCertificate -> ShowS
Prelude.Show, forall x. Rep ListTagsForCertificate x -> ListTagsForCertificate
forall x. ListTagsForCertificate -> Rep ListTagsForCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTagsForCertificate x -> ListTagsForCertificate
$cfrom :: forall x. ListTagsForCertificate -> Rep ListTagsForCertificate x
Prelude.Generic)

-- |
-- Create a value of 'ListTagsForCertificate' 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:
--
-- 'certificateArn', 'listTagsForCertificate_certificateArn' - String that contains the ARN of the ACM certificate for which you want
-- to list the tags. This must have the following form:
--
-- @arn:aws:acm:region:123456789012:certificate\/12345678-1234-1234-1234-123456789012@
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
newListTagsForCertificate ::
  -- | 'certificateArn'
  Prelude.Text ->
  ListTagsForCertificate
newListTagsForCertificate :: Text -> ListTagsForCertificate
newListTagsForCertificate Text
pCertificateArn_ =
  ListTagsForCertificate'
    { $sel:certificateArn:ListTagsForCertificate' :: Text
certificateArn =
        Text
pCertificateArn_
    }

-- | String that contains the ARN of the ACM certificate for which you want
-- to list the tags. This must have the following form:
--
-- @arn:aws:acm:region:123456789012:certificate\/12345678-1234-1234-1234-123456789012@
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
listTagsForCertificate_certificateArn :: Lens.Lens' ListTagsForCertificate Prelude.Text
listTagsForCertificate_certificateArn :: Lens' ListTagsForCertificate Text
listTagsForCertificate_certificateArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsForCertificate' {Text
certificateArn :: Text
$sel:certificateArn:ListTagsForCertificate' :: ListTagsForCertificate -> Text
certificateArn} -> Text
certificateArn) (\s :: ListTagsForCertificate
s@ListTagsForCertificate' {} Text
a -> ListTagsForCertificate
s {$sel:certificateArn:ListTagsForCertificate' :: Text
certificateArn = Text
a} :: ListTagsForCertificate)

instance Core.AWSRequest ListTagsForCertificate where
  type
    AWSResponse ListTagsForCertificate =
      ListTagsForCertificateResponse
  request :: (Service -> Service)
-> ListTagsForCertificate -> Request ListTagsForCertificate
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 ListTagsForCertificate
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListTagsForCertificate)))
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 (NonEmpty Tag) -> Int -> ListTagsForCertificateResponse
ListTagsForCertificateResponse'
            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 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 ListTagsForCertificate where
  hashWithSalt :: Int -> ListTagsForCertificate -> Int
hashWithSalt Int
_salt ListTagsForCertificate' {Text
certificateArn :: Text
$sel:certificateArn:ListTagsForCertificate' :: ListTagsForCertificate -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
certificateArn

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

instance Data.ToHeaders ListTagsForCertificate where
  toHeaders :: ListTagsForCertificate -> 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
"CertificateManager.ListTagsForCertificate" ::
                          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 ListTagsForCertificate where
  toJSON :: ListTagsForCertificate -> Value
toJSON ListTagsForCertificate' {Text
certificateArn :: Text
$sel:certificateArn:ListTagsForCertificate' :: ListTagsForCertificate -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"CertificateArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
certificateArn)
          ]
      )

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

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

-- | /See:/ 'newListTagsForCertificateResponse' smart constructor.
data ListTagsForCertificateResponse = ListTagsForCertificateResponse'
  { -- | The key-value pairs that define the applied tags.
    ListTagsForCertificateResponse -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | The response's http status code.
    ListTagsForCertificateResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListTagsForCertificateResponse
-> ListTagsForCertificateResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTagsForCertificateResponse
-> ListTagsForCertificateResponse -> Bool
$c/= :: ListTagsForCertificateResponse
-> ListTagsForCertificateResponse -> Bool
== :: ListTagsForCertificateResponse
-> ListTagsForCertificateResponse -> Bool
$c== :: ListTagsForCertificateResponse
-> ListTagsForCertificateResponse -> Bool
Prelude.Eq, ReadPrec [ListTagsForCertificateResponse]
ReadPrec ListTagsForCertificateResponse
Int -> ReadS ListTagsForCertificateResponse
ReadS [ListTagsForCertificateResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTagsForCertificateResponse]
$creadListPrec :: ReadPrec [ListTagsForCertificateResponse]
readPrec :: ReadPrec ListTagsForCertificateResponse
$creadPrec :: ReadPrec ListTagsForCertificateResponse
readList :: ReadS [ListTagsForCertificateResponse]
$creadList :: ReadS [ListTagsForCertificateResponse]
readsPrec :: Int -> ReadS ListTagsForCertificateResponse
$creadsPrec :: Int -> ReadS ListTagsForCertificateResponse
Prelude.Read, Int -> ListTagsForCertificateResponse -> ShowS
[ListTagsForCertificateResponse] -> ShowS
ListTagsForCertificateResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTagsForCertificateResponse] -> ShowS
$cshowList :: [ListTagsForCertificateResponse] -> ShowS
show :: ListTagsForCertificateResponse -> String
$cshow :: ListTagsForCertificateResponse -> String
showsPrec :: Int -> ListTagsForCertificateResponse -> ShowS
$cshowsPrec :: Int -> ListTagsForCertificateResponse -> ShowS
Prelude.Show, forall x.
Rep ListTagsForCertificateResponse x
-> ListTagsForCertificateResponse
forall x.
ListTagsForCertificateResponse
-> Rep ListTagsForCertificateResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListTagsForCertificateResponse x
-> ListTagsForCertificateResponse
$cfrom :: forall x.
ListTagsForCertificateResponse
-> Rep ListTagsForCertificateResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListTagsForCertificateResponse' 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', 'listTagsForCertificateResponse_tags' - The key-value pairs that define the applied tags.
--
-- 'httpStatus', 'listTagsForCertificateResponse_httpStatus' - The response's http status code.
newListTagsForCertificateResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListTagsForCertificateResponse
newListTagsForCertificateResponse :: Int -> ListTagsForCertificateResponse
newListTagsForCertificateResponse Int
pHttpStatus_ =
  ListTagsForCertificateResponse'
    { $sel:tags:ListTagsForCertificateResponse' :: Maybe (NonEmpty Tag)
tags =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListTagsForCertificateResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The key-value pairs that define the applied tags.
listTagsForCertificateResponse_tags :: Lens.Lens' ListTagsForCertificateResponse (Prelude.Maybe (Prelude.NonEmpty Tag))
listTagsForCertificateResponse_tags :: Lens' ListTagsForCertificateResponse (Maybe (NonEmpty Tag))
listTagsForCertificateResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsForCertificateResponse' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:ListTagsForCertificateResponse' :: ListTagsForCertificateResponse -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: ListTagsForCertificateResponse
s@ListTagsForCertificateResponse' {} Maybe (NonEmpty Tag)
a -> ListTagsForCertificateResponse
s {$sel:tags:ListTagsForCertificateResponse' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
a} :: ListTagsForCertificateResponse) 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.
listTagsForCertificateResponse_httpStatus :: Lens.Lens' ListTagsForCertificateResponse Prelude.Int
listTagsForCertificateResponse_httpStatus :: Lens' ListTagsForCertificateResponse Int
listTagsForCertificateResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsForCertificateResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListTagsForCertificateResponse' :: ListTagsForCertificateResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListTagsForCertificateResponse
s@ListTagsForCertificateResponse' {} Int
a -> ListTagsForCertificateResponse
s {$sel:httpStatus:ListTagsForCertificateResponse' :: Int
httpStatus = Int
a} :: ListTagsForCertificateResponse)

instance
  Prelude.NFData
    ListTagsForCertificateResponse
  where
  rnf :: ListTagsForCertificateResponse -> ()
rnf ListTagsForCertificateResponse' {Int
Maybe (NonEmpty Tag)
httpStatus :: Int
tags :: Maybe (NonEmpty Tag)
$sel:httpStatus:ListTagsForCertificateResponse' :: ListTagsForCertificateResponse -> Int
$sel:tags:ListTagsForCertificateResponse' :: ListTagsForCertificateResponse -> Maybe (NonEmpty Tag)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Tag)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus