{-# 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.Route53.ListTagsForResources
-- 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 tags for up to 10 health checks or hosted zones.
--
-- For information about using tags for cost allocation, see
-- <https://docs.aws.amazon.com/awsaccountbilling/latest/aboutv2/cost-alloc-tags.html Using Cost Allocation Tags>
-- in the /Billing and Cost Management User Guide/.
module Amazonka.Route53.ListTagsForResources
  ( -- * Creating a Request
    ListTagsForResources (..),
    newListTagsForResources,

    -- * Request Lenses
    listTagsForResources_resourceType,
    listTagsForResources_resourceIds,

    -- * Destructuring the Response
    ListTagsForResourcesResponse (..),
    newListTagsForResourcesResponse,

    -- * Response Lenses
    listTagsForResourcesResponse_httpStatus,
    listTagsForResourcesResponse_resourceTagSets,
  )
where

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

-- | A complex type that contains information about the health checks or
-- hosted zones for which you want to list tags.
--
-- /See:/ 'newListTagsForResources' smart constructor.
data ListTagsForResources = ListTagsForResources'
  { -- | The type of the resources.
    --
    -- -   The resource type for health checks is @healthcheck@.
    --
    -- -   The resource type for hosted zones is @hostedzone@.
    ListTagsForResources -> TagResourceType
resourceType :: TagResourceType,
    -- | A complex type that contains the ResourceId element for each resource
    -- for which you want to get a list of tags.
    ListTagsForResources -> NonEmpty Text
resourceIds :: Prelude.NonEmpty Prelude.Text
  }
  deriving (ListTagsForResources -> ListTagsForResources -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTagsForResources -> ListTagsForResources -> Bool
$c/= :: ListTagsForResources -> ListTagsForResources -> Bool
== :: ListTagsForResources -> ListTagsForResources -> Bool
$c== :: ListTagsForResources -> ListTagsForResources -> Bool
Prelude.Eq, ReadPrec [ListTagsForResources]
ReadPrec ListTagsForResources
Int -> ReadS ListTagsForResources
ReadS [ListTagsForResources]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTagsForResources]
$creadListPrec :: ReadPrec [ListTagsForResources]
readPrec :: ReadPrec ListTagsForResources
$creadPrec :: ReadPrec ListTagsForResources
readList :: ReadS [ListTagsForResources]
$creadList :: ReadS [ListTagsForResources]
readsPrec :: Int -> ReadS ListTagsForResources
$creadsPrec :: Int -> ReadS ListTagsForResources
Prelude.Read, Int -> ListTagsForResources -> ShowS
[ListTagsForResources] -> ShowS
ListTagsForResources -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTagsForResources] -> ShowS
$cshowList :: [ListTagsForResources] -> ShowS
show :: ListTagsForResources -> String
$cshow :: ListTagsForResources -> String
showsPrec :: Int -> ListTagsForResources -> ShowS
$cshowsPrec :: Int -> ListTagsForResources -> ShowS
Prelude.Show, forall x. Rep ListTagsForResources x -> ListTagsForResources
forall x. ListTagsForResources -> Rep ListTagsForResources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTagsForResources x -> ListTagsForResources
$cfrom :: forall x. ListTagsForResources -> Rep ListTagsForResources x
Prelude.Generic)

-- |
-- Create a value of 'ListTagsForResources' 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:
--
-- 'resourceType', 'listTagsForResources_resourceType' - The type of the resources.
--
-- -   The resource type for health checks is @healthcheck@.
--
-- -   The resource type for hosted zones is @hostedzone@.
--
-- 'resourceIds', 'listTagsForResources_resourceIds' - A complex type that contains the ResourceId element for each resource
-- for which you want to get a list of tags.
newListTagsForResources ::
  -- | 'resourceType'
  TagResourceType ->
  -- | 'resourceIds'
  Prelude.NonEmpty Prelude.Text ->
  ListTagsForResources
newListTagsForResources :: TagResourceType -> NonEmpty Text -> ListTagsForResources
newListTagsForResources TagResourceType
pResourceType_ NonEmpty Text
pResourceIds_ =
  ListTagsForResources'
    { $sel:resourceType:ListTagsForResources' :: TagResourceType
resourceType =
        TagResourceType
pResourceType_,
      $sel:resourceIds:ListTagsForResources' :: NonEmpty Text
resourceIds = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pResourceIds_
    }

-- | The type of the resources.
--
-- -   The resource type for health checks is @healthcheck@.
--
-- -   The resource type for hosted zones is @hostedzone@.
listTagsForResources_resourceType :: Lens.Lens' ListTagsForResources TagResourceType
listTagsForResources_resourceType :: Lens' ListTagsForResources TagResourceType
listTagsForResources_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsForResources' {TagResourceType
resourceType :: TagResourceType
$sel:resourceType:ListTagsForResources' :: ListTagsForResources -> TagResourceType
resourceType} -> TagResourceType
resourceType) (\s :: ListTagsForResources
s@ListTagsForResources' {} TagResourceType
a -> ListTagsForResources
s {$sel:resourceType:ListTagsForResources' :: TagResourceType
resourceType = TagResourceType
a} :: ListTagsForResources)

-- | A complex type that contains the ResourceId element for each resource
-- for which you want to get a list of tags.
listTagsForResources_resourceIds :: Lens.Lens' ListTagsForResources (Prelude.NonEmpty Prelude.Text)
listTagsForResources_resourceIds :: Lens' ListTagsForResources (NonEmpty Text)
listTagsForResources_resourceIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsForResources' {NonEmpty Text
resourceIds :: NonEmpty Text
$sel:resourceIds:ListTagsForResources' :: ListTagsForResources -> NonEmpty Text
resourceIds} -> NonEmpty Text
resourceIds) (\s :: ListTagsForResources
s@ListTagsForResources' {} NonEmpty Text
a -> ListTagsForResources
s {$sel:resourceIds:ListTagsForResources' :: NonEmpty Text
resourceIds = NonEmpty Text
a} :: ListTagsForResources) 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 Core.AWSRequest ListTagsForResources where
  type
    AWSResponse ListTagsForResources =
      ListTagsForResourcesResponse
  request :: (Service -> Service)
-> ListTagsForResources -> Request ListTagsForResources
request Service -> Service
overrides =
    forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.postXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListTagsForResources
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListTagsForResources)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> [ResourceTagSet] -> ListTagsForResourcesResponse
ListTagsForResourcesResponse'
            forall (f :: * -> *) a b. Functor 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.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ResourceTagSets"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"ResourceTagSet"
                        )
      )

instance Prelude.Hashable ListTagsForResources where
  hashWithSalt :: Int -> ListTagsForResources -> Int
hashWithSalt Int
_salt ListTagsForResources' {NonEmpty Text
TagResourceType
resourceIds :: NonEmpty Text
resourceType :: TagResourceType
$sel:resourceIds:ListTagsForResources' :: ListTagsForResources -> NonEmpty Text
$sel:resourceType:ListTagsForResources' :: ListTagsForResources -> TagResourceType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TagResourceType
resourceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
resourceIds

instance Prelude.NFData ListTagsForResources where
  rnf :: ListTagsForResources -> ()
rnf ListTagsForResources' {NonEmpty Text
TagResourceType
resourceIds :: NonEmpty Text
resourceType :: TagResourceType
$sel:resourceIds:ListTagsForResources' :: ListTagsForResources -> NonEmpty Text
$sel:resourceType:ListTagsForResources' :: ListTagsForResources -> TagResourceType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf TagResourceType
resourceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
resourceIds

instance Data.ToElement ListTagsForResources where
  toElement :: ListTagsForResources -> Element
toElement =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{https://route53.amazonaws.com/doc/2013-04-01/}ListTagsForResourcesRequest"

instance Data.ToHeaders ListTagsForResources where
  toHeaders :: ListTagsForResources -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath ListTagsForResources where
  toPath :: ListTagsForResources -> ByteString
toPath ListTagsForResources' {NonEmpty Text
TagResourceType
resourceIds :: NonEmpty Text
resourceType :: TagResourceType
$sel:resourceIds:ListTagsForResources' :: ListTagsForResources -> NonEmpty Text
$sel:resourceType:ListTagsForResources' :: ListTagsForResources -> TagResourceType
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2013-04-01/tags/", forall a. ToByteString a => a -> ByteString
Data.toBS TagResourceType
resourceType]

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

instance Data.ToXML ListTagsForResources where
  toXML :: ListTagsForResources -> XML
toXML ListTagsForResources' {NonEmpty Text
TagResourceType
resourceIds :: NonEmpty Text
resourceType :: TagResourceType
$sel:resourceIds:ListTagsForResources' :: ListTagsForResources -> NonEmpty Text
$sel:resourceType:ListTagsForResources' :: ListTagsForResources -> TagResourceType
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ Name
"ResourceIds"
          forall a. ToXML a => Name -> a -> XML
Data.@= forall a. (IsList a, ToXML (Item a)) => Name -> a -> XML
Data.toXMLList Name
"ResourceId" NonEmpty Text
resourceIds
      ]

-- | A complex type containing tags for the specified resources.
--
-- /See:/ 'newListTagsForResourcesResponse' smart constructor.
data ListTagsForResourcesResponse = ListTagsForResourcesResponse'
  { -- | The response's http status code.
    ListTagsForResourcesResponse -> Int
httpStatus :: Prelude.Int,
    -- | A list of @ResourceTagSet@s containing tags associated with the
    -- specified resources.
    ListTagsForResourcesResponse -> [ResourceTagSet]
resourceTagSets :: [ResourceTagSet]
  }
  deriving (ListTagsForResourcesResponse
-> ListTagsForResourcesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTagsForResourcesResponse
-> ListTagsForResourcesResponse -> Bool
$c/= :: ListTagsForResourcesResponse
-> ListTagsForResourcesResponse -> Bool
== :: ListTagsForResourcesResponse
-> ListTagsForResourcesResponse -> Bool
$c== :: ListTagsForResourcesResponse
-> ListTagsForResourcesResponse -> Bool
Prelude.Eq, ReadPrec [ListTagsForResourcesResponse]
ReadPrec ListTagsForResourcesResponse
Int -> ReadS ListTagsForResourcesResponse
ReadS [ListTagsForResourcesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTagsForResourcesResponse]
$creadListPrec :: ReadPrec [ListTagsForResourcesResponse]
readPrec :: ReadPrec ListTagsForResourcesResponse
$creadPrec :: ReadPrec ListTagsForResourcesResponse
readList :: ReadS [ListTagsForResourcesResponse]
$creadList :: ReadS [ListTagsForResourcesResponse]
readsPrec :: Int -> ReadS ListTagsForResourcesResponse
$creadsPrec :: Int -> ReadS ListTagsForResourcesResponse
Prelude.Read, Int -> ListTagsForResourcesResponse -> ShowS
[ListTagsForResourcesResponse] -> ShowS
ListTagsForResourcesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTagsForResourcesResponse] -> ShowS
$cshowList :: [ListTagsForResourcesResponse] -> ShowS
show :: ListTagsForResourcesResponse -> String
$cshow :: ListTagsForResourcesResponse -> String
showsPrec :: Int -> ListTagsForResourcesResponse -> ShowS
$cshowsPrec :: Int -> ListTagsForResourcesResponse -> ShowS
Prelude.Show, forall x.
Rep ListTagsForResourcesResponse x -> ListTagsForResourcesResponse
forall x.
ListTagsForResourcesResponse -> Rep ListTagsForResourcesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListTagsForResourcesResponse x -> ListTagsForResourcesResponse
$cfrom :: forall x.
ListTagsForResourcesResponse -> Rep ListTagsForResourcesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListTagsForResourcesResponse' 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:
--
-- 'httpStatus', 'listTagsForResourcesResponse_httpStatus' - The response's http status code.
--
-- 'resourceTagSets', 'listTagsForResourcesResponse_resourceTagSets' - A list of @ResourceTagSet@s containing tags associated with the
-- specified resources.
newListTagsForResourcesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListTagsForResourcesResponse
newListTagsForResourcesResponse :: Int -> ListTagsForResourcesResponse
newListTagsForResourcesResponse Int
pHttpStatus_ =
  ListTagsForResourcesResponse'
    { $sel:httpStatus:ListTagsForResourcesResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:resourceTagSets:ListTagsForResourcesResponse' :: [ResourceTagSet]
resourceTagSets = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | A list of @ResourceTagSet@s containing tags associated with the
-- specified resources.
listTagsForResourcesResponse_resourceTagSets :: Lens.Lens' ListTagsForResourcesResponse [ResourceTagSet]
listTagsForResourcesResponse_resourceTagSets :: Lens' ListTagsForResourcesResponse [ResourceTagSet]
listTagsForResourcesResponse_resourceTagSets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTagsForResourcesResponse' {[ResourceTagSet]
resourceTagSets :: [ResourceTagSet]
$sel:resourceTagSets:ListTagsForResourcesResponse' :: ListTagsForResourcesResponse -> [ResourceTagSet]
resourceTagSets} -> [ResourceTagSet]
resourceTagSets) (\s :: ListTagsForResourcesResponse
s@ListTagsForResourcesResponse' {} [ResourceTagSet]
a -> ListTagsForResourcesResponse
s {$sel:resourceTagSets:ListTagsForResourcesResponse' :: [ResourceTagSet]
resourceTagSets = [ResourceTagSet]
a} :: ListTagsForResourcesResponse) 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 ListTagsForResourcesResponse where
  rnf :: ListTagsForResourcesResponse -> ()
rnf ListTagsForResourcesResponse' {Int
[ResourceTagSet]
resourceTagSets :: [ResourceTagSet]
httpStatus :: Int
$sel:resourceTagSets:ListTagsForResourcesResponse' :: ListTagsForResourcesResponse -> [ResourceTagSet]
$sel:httpStatus:ListTagsForResourcesResponse' :: ListTagsForResourcesResponse -> Int
..} =
    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 [ResourceTagSet]
resourceTagSets