{-# 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.CostExplorer.ListCostAllocationTags
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Get a list of cost allocation tags. All inputs in the API are optional
-- and serve as filters. By default, all cost allocation tags are returned.
module Amazonka.CostExplorer.ListCostAllocationTags
  ( -- * Creating a Request
    ListCostAllocationTags (..),
    newListCostAllocationTags,

    -- * Request Lenses
    listCostAllocationTags_maxResults,
    listCostAllocationTags_nextToken,
    listCostAllocationTags_status,
    listCostAllocationTags_tagKeys,
    listCostAllocationTags_type,

    -- * Destructuring the Response
    ListCostAllocationTagsResponse (..),
    newListCostAllocationTagsResponse,

    -- * Response Lenses
    listCostAllocationTagsResponse_costAllocationTags,
    listCostAllocationTagsResponse_nextToken,
    listCostAllocationTagsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.CostExplorer.Types
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:/ 'newListCostAllocationTags' smart constructor.
data ListCostAllocationTags = ListCostAllocationTags'
  { -- | The maximum number of objects that are returned for this request. By
    -- default, the request returns 100 results.
    ListCostAllocationTags -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token to retrieve the next set of results. Amazon Web Services
    -- provides the token when the response from a previous call has more
    -- results than the maximum page size.
    ListCostAllocationTags -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The status of cost allocation tag keys that are returned for this
    -- request.
    ListCostAllocationTags -> Maybe CostAllocationTagStatus
status :: Prelude.Maybe CostAllocationTagStatus,
    -- | The list of cost allocation tag keys that are returned for this request.
    ListCostAllocationTags -> Maybe (NonEmpty Text)
tagKeys :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The type of @CostAllocationTag@ object that are returned for this
    -- request. The @AWSGenerated@ type tags are tags that Amazon Web Services
    -- defines and applies to support Amazon Web Services resources for cost
    -- allocation purposes. The @UserDefined@ type tags are tags that you
    -- define, create, and apply to resources.
    ListCostAllocationTags -> Maybe CostAllocationTagType
type' :: Prelude.Maybe CostAllocationTagType
  }
  deriving (ListCostAllocationTags -> ListCostAllocationTags -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCostAllocationTags -> ListCostAllocationTags -> Bool
$c/= :: ListCostAllocationTags -> ListCostAllocationTags -> Bool
== :: ListCostAllocationTags -> ListCostAllocationTags -> Bool
$c== :: ListCostAllocationTags -> ListCostAllocationTags -> Bool
Prelude.Eq, ReadPrec [ListCostAllocationTags]
ReadPrec ListCostAllocationTags
Int -> ReadS ListCostAllocationTags
ReadS [ListCostAllocationTags]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCostAllocationTags]
$creadListPrec :: ReadPrec [ListCostAllocationTags]
readPrec :: ReadPrec ListCostAllocationTags
$creadPrec :: ReadPrec ListCostAllocationTags
readList :: ReadS [ListCostAllocationTags]
$creadList :: ReadS [ListCostAllocationTags]
readsPrec :: Int -> ReadS ListCostAllocationTags
$creadsPrec :: Int -> ReadS ListCostAllocationTags
Prelude.Read, Int -> ListCostAllocationTags -> ShowS
[ListCostAllocationTags] -> ShowS
ListCostAllocationTags -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCostAllocationTags] -> ShowS
$cshowList :: [ListCostAllocationTags] -> ShowS
show :: ListCostAllocationTags -> String
$cshow :: ListCostAllocationTags -> String
showsPrec :: Int -> ListCostAllocationTags -> ShowS
$cshowsPrec :: Int -> ListCostAllocationTags -> ShowS
Prelude.Show, forall x. Rep ListCostAllocationTags x -> ListCostAllocationTags
forall x. ListCostAllocationTags -> Rep ListCostAllocationTags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListCostAllocationTags x -> ListCostAllocationTags
$cfrom :: forall x. ListCostAllocationTags -> Rep ListCostAllocationTags x
Prelude.Generic)

-- |
-- Create a value of 'ListCostAllocationTags' 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', 'listCostAllocationTags_maxResults' - The maximum number of objects that are returned for this request. By
-- default, the request returns 100 results.
--
-- 'nextToken', 'listCostAllocationTags_nextToken' - The token to retrieve the next set of results. Amazon Web Services
-- provides the token when the response from a previous call has more
-- results than the maximum page size.
--
-- 'status', 'listCostAllocationTags_status' - The status of cost allocation tag keys that are returned for this
-- request.
--
-- 'tagKeys', 'listCostAllocationTags_tagKeys' - The list of cost allocation tag keys that are returned for this request.
--
-- 'type'', 'listCostAllocationTags_type' - The type of @CostAllocationTag@ object that are returned for this
-- request. The @AWSGenerated@ type tags are tags that Amazon Web Services
-- defines and applies to support Amazon Web Services resources for cost
-- allocation purposes. The @UserDefined@ type tags are tags that you
-- define, create, and apply to resources.
newListCostAllocationTags ::
  ListCostAllocationTags
newListCostAllocationTags :: ListCostAllocationTags
newListCostAllocationTags =
  ListCostAllocationTags'
    { $sel:maxResults:ListCostAllocationTags' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCostAllocationTags' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:status:ListCostAllocationTags' :: Maybe CostAllocationTagStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:tagKeys:ListCostAllocationTags' :: Maybe (NonEmpty Text)
tagKeys = forall a. Maybe a
Prelude.Nothing,
      $sel:type':ListCostAllocationTags' :: Maybe CostAllocationTagType
type' = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of objects that are returned for this request. By
-- default, the request returns 100 results.
listCostAllocationTags_maxResults :: Lens.Lens' ListCostAllocationTags (Prelude.Maybe Prelude.Natural)
listCostAllocationTags_maxResults :: Lens' ListCostAllocationTags (Maybe Natural)
listCostAllocationTags_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCostAllocationTags' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListCostAllocationTags
s@ListCostAllocationTags' {} Maybe Natural
a -> ListCostAllocationTags
s {$sel:maxResults:ListCostAllocationTags' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListCostAllocationTags)

-- | The token to retrieve the next set of results. Amazon Web Services
-- provides the token when the response from a previous call has more
-- results than the maximum page size.
listCostAllocationTags_nextToken :: Lens.Lens' ListCostAllocationTags (Prelude.Maybe Prelude.Text)
listCostAllocationTags_nextToken :: Lens' ListCostAllocationTags (Maybe Text)
listCostAllocationTags_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCostAllocationTags' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListCostAllocationTags
s@ListCostAllocationTags' {} Maybe Text
a -> ListCostAllocationTags
s {$sel:nextToken:ListCostAllocationTags' :: Maybe Text
nextToken = Maybe Text
a} :: ListCostAllocationTags)

-- | The status of cost allocation tag keys that are returned for this
-- request.
listCostAllocationTags_status :: Lens.Lens' ListCostAllocationTags (Prelude.Maybe CostAllocationTagStatus)
listCostAllocationTags_status :: Lens' ListCostAllocationTags (Maybe CostAllocationTagStatus)
listCostAllocationTags_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCostAllocationTags' {Maybe CostAllocationTagStatus
status :: Maybe CostAllocationTagStatus
$sel:status:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe CostAllocationTagStatus
status} -> Maybe CostAllocationTagStatus
status) (\s :: ListCostAllocationTags
s@ListCostAllocationTags' {} Maybe CostAllocationTagStatus
a -> ListCostAllocationTags
s {$sel:status:ListCostAllocationTags' :: Maybe CostAllocationTagStatus
status = Maybe CostAllocationTagStatus
a} :: ListCostAllocationTags)

-- | The list of cost allocation tag keys that are returned for this request.
listCostAllocationTags_tagKeys :: Lens.Lens' ListCostAllocationTags (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
listCostAllocationTags_tagKeys :: Lens' ListCostAllocationTags (Maybe (NonEmpty Text))
listCostAllocationTags_tagKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCostAllocationTags' {Maybe (NonEmpty Text)
tagKeys :: Maybe (NonEmpty Text)
$sel:tagKeys:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe (NonEmpty Text)
tagKeys} -> Maybe (NonEmpty Text)
tagKeys) (\s :: ListCostAllocationTags
s@ListCostAllocationTags' {} Maybe (NonEmpty Text)
a -> ListCostAllocationTags
s {$sel:tagKeys:ListCostAllocationTags' :: Maybe (NonEmpty Text)
tagKeys = Maybe (NonEmpty Text)
a} :: ListCostAllocationTags) 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 type of @CostAllocationTag@ object that are returned for this
-- request. The @AWSGenerated@ type tags are tags that Amazon Web Services
-- defines and applies to support Amazon Web Services resources for cost
-- allocation purposes. The @UserDefined@ type tags are tags that you
-- define, create, and apply to resources.
listCostAllocationTags_type :: Lens.Lens' ListCostAllocationTags (Prelude.Maybe CostAllocationTagType)
listCostAllocationTags_type :: Lens' ListCostAllocationTags (Maybe CostAllocationTagType)
listCostAllocationTags_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCostAllocationTags' {Maybe CostAllocationTagType
type' :: Maybe CostAllocationTagType
$sel:type':ListCostAllocationTags' :: ListCostAllocationTags -> Maybe CostAllocationTagType
type'} -> Maybe CostAllocationTagType
type') (\s :: ListCostAllocationTags
s@ListCostAllocationTags' {} Maybe CostAllocationTagType
a -> ListCostAllocationTags
s {$sel:type':ListCostAllocationTags' :: Maybe CostAllocationTagType
type' = Maybe CostAllocationTagType
a} :: ListCostAllocationTags)

instance Core.AWSRequest ListCostAllocationTags where
  type
    AWSResponse ListCostAllocationTags =
      ListCostAllocationTagsResponse
  request :: (Service -> Service)
-> ListCostAllocationTags -> Request ListCostAllocationTags
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 ListCostAllocationTags
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListCostAllocationTags)))
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 [CostAllocationTag]
-> Maybe Text -> Int -> ListCostAllocationTagsResponse
ListCostAllocationTagsResponse'
            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
"CostAllocationTags"
                            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
"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))
      )

instance Prelude.Hashable ListCostAllocationTags where
  hashWithSalt :: Int -> ListCostAllocationTags -> Int
hashWithSalt Int
_salt ListCostAllocationTags' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Maybe CostAllocationTagStatus
Maybe CostAllocationTagType
type' :: Maybe CostAllocationTagType
tagKeys :: Maybe (NonEmpty Text)
status :: Maybe CostAllocationTagStatus
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:type':ListCostAllocationTags' :: ListCostAllocationTags -> Maybe CostAllocationTagType
$sel:tagKeys:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe (NonEmpty Text)
$sel:status:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe CostAllocationTagStatus
$sel:nextToken:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe Text
$sel:maxResults:ListCostAllocationTags' :: ListCostAllocationTags -> 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` Maybe CostAllocationTagStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
tagKeys
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CostAllocationTagType
type'

instance Prelude.NFData ListCostAllocationTags where
  rnf :: ListCostAllocationTags -> ()
rnf ListCostAllocationTags' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Maybe CostAllocationTagStatus
Maybe CostAllocationTagType
type' :: Maybe CostAllocationTagType
tagKeys :: Maybe (NonEmpty Text)
status :: Maybe CostAllocationTagStatus
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:type':ListCostAllocationTags' :: ListCostAllocationTags -> Maybe CostAllocationTagType
$sel:tagKeys:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe (NonEmpty Text)
$sel:status:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe CostAllocationTagStatus
$sel:nextToken:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe Text
$sel:maxResults:ListCostAllocationTags' :: ListCostAllocationTags -> 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 Maybe CostAllocationTagStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
tagKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CostAllocationTagType
type'

instance Data.ToHeaders ListCostAllocationTags where
  toHeaders :: ListCostAllocationTags -> 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
"AWSInsightsIndexService.ListCostAllocationTags" ::
                          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 ListCostAllocationTags where
  toJSON :: ListCostAllocationTags -> Value
toJSON ListCostAllocationTags' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Maybe CostAllocationTagStatus
Maybe CostAllocationTagType
type' :: Maybe CostAllocationTagType
tagKeys :: Maybe (NonEmpty Text)
status :: Maybe CostAllocationTagStatus
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:type':ListCostAllocationTags' :: ListCostAllocationTags -> Maybe CostAllocationTagType
$sel:tagKeys:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe (NonEmpty Text)
$sel:status:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe CostAllocationTagStatus
$sel:nextToken:ListCostAllocationTags' :: ListCostAllocationTags -> Maybe Text
$sel:maxResults:ListCostAllocationTags' :: ListCostAllocationTags -> 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,
            (Key
"Status" 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 CostAllocationTagStatus
status,
            (Key
"TagKeys" 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 (NonEmpty Text)
tagKeys,
            (Key
"Type" 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 CostAllocationTagType
type'
          ]
      )

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

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

-- | /See:/ 'newListCostAllocationTagsResponse' smart constructor.
data ListCostAllocationTagsResponse = ListCostAllocationTagsResponse'
  { -- | A list of cost allocation tags that includes the detailed metadata for
    -- each one.
    ListCostAllocationTagsResponse -> Maybe [CostAllocationTag]
costAllocationTags :: Prelude.Maybe [CostAllocationTag],
    -- | The token to retrieve the next set of results. Amazon Web Services
    -- provides the token when the response from a previous call has more
    -- results than the maximum page size.
    ListCostAllocationTagsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListCostAllocationTagsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListCostAllocationTagsResponse
-> ListCostAllocationTagsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCostAllocationTagsResponse
-> ListCostAllocationTagsResponse -> Bool
$c/= :: ListCostAllocationTagsResponse
-> ListCostAllocationTagsResponse -> Bool
== :: ListCostAllocationTagsResponse
-> ListCostAllocationTagsResponse -> Bool
$c== :: ListCostAllocationTagsResponse
-> ListCostAllocationTagsResponse -> Bool
Prelude.Eq, ReadPrec [ListCostAllocationTagsResponse]
ReadPrec ListCostAllocationTagsResponse
Int -> ReadS ListCostAllocationTagsResponse
ReadS [ListCostAllocationTagsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCostAllocationTagsResponse]
$creadListPrec :: ReadPrec [ListCostAllocationTagsResponse]
readPrec :: ReadPrec ListCostAllocationTagsResponse
$creadPrec :: ReadPrec ListCostAllocationTagsResponse
readList :: ReadS [ListCostAllocationTagsResponse]
$creadList :: ReadS [ListCostAllocationTagsResponse]
readsPrec :: Int -> ReadS ListCostAllocationTagsResponse
$creadsPrec :: Int -> ReadS ListCostAllocationTagsResponse
Prelude.Read, Int -> ListCostAllocationTagsResponse -> ShowS
[ListCostAllocationTagsResponse] -> ShowS
ListCostAllocationTagsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCostAllocationTagsResponse] -> ShowS
$cshowList :: [ListCostAllocationTagsResponse] -> ShowS
show :: ListCostAllocationTagsResponse -> String
$cshow :: ListCostAllocationTagsResponse -> String
showsPrec :: Int -> ListCostAllocationTagsResponse -> ShowS
$cshowsPrec :: Int -> ListCostAllocationTagsResponse -> ShowS
Prelude.Show, forall x.
Rep ListCostAllocationTagsResponse x
-> ListCostAllocationTagsResponse
forall x.
ListCostAllocationTagsResponse
-> Rep ListCostAllocationTagsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListCostAllocationTagsResponse x
-> ListCostAllocationTagsResponse
$cfrom :: forall x.
ListCostAllocationTagsResponse
-> Rep ListCostAllocationTagsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListCostAllocationTagsResponse' 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:
--
-- 'costAllocationTags', 'listCostAllocationTagsResponse_costAllocationTags' - A list of cost allocation tags that includes the detailed metadata for
-- each one.
--
-- 'nextToken', 'listCostAllocationTagsResponse_nextToken' - The token to retrieve the next set of results. Amazon Web Services
-- provides the token when the response from a previous call has more
-- results than the maximum page size.
--
-- 'httpStatus', 'listCostAllocationTagsResponse_httpStatus' - The response's http status code.
newListCostAllocationTagsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListCostAllocationTagsResponse
newListCostAllocationTagsResponse :: Int -> ListCostAllocationTagsResponse
newListCostAllocationTagsResponse Int
pHttpStatus_ =
  ListCostAllocationTagsResponse'
    { $sel:costAllocationTags:ListCostAllocationTagsResponse' :: Maybe [CostAllocationTag]
costAllocationTags =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCostAllocationTagsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListCostAllocationTagsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of cost allocation tags that includes the detailed metadata for
-- each one.
listCostAllocationTagsResponse_costAllocationTags :: Lens.Lens' ListCostAllocationTagsResponse (Prelude.Maybe [CostAllocationTag])
listCostAllocationTagsResponse_costAllocationTags :: Lens' ListCostAllocationTagsResponse (Maybe [CostAllocationTag])
listCostAllocationTagsResponse_costAllocationTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCostAllocationTagsResponse' {Maybe [CostAllocationTag]
costAllocationTags :: Maybe [CostAllocationTag]
$sel:costAllocationTags:ListCostAllocationTagsResponse' :: ListCostAllocationTagsResponse -> Maybe [CostAllocationTag]
costAllocationTags} -> Maybe [CostAllocationTag]
costAllocationTags) (\s :: ListCostAllocationTagsResponse
s@ListCostAllocationTagsResponse' {} Maybe [CostAllocationTag]
a -> ListCostAllocationTagsResponse
s {$sel:costAllocationTags:ListCostAllocationTagsResponse' :: Maybe [CostAllocationTag]
costAllocationTags = Maybe [CostAllocationTag]
a} :: ListCostAllocationTagsResponse) 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 token to retrieve the next set of results. Amazon Web Services
-- provides the token when the response from a previous call has more
-- results than the maximum page size.
listCostAllocationTagsResponse_nextToken :: Lens.Lens' ListCostAllocationTagsResponse (Prelude.Maybe Prelude.Text)
listCostAllocationTagsResponse_nextToken :: Lens' ListCostAllocationTagsResponse (Maybe Text)
listCostAllocationTagsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCostAllocationTagsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListCostAllocationTagsResponse' :: ListCostAllocationTagsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListCostAllocationTagsResponse
s@ListCostAllocationTagsResponse' {} Maybe Text
a -> ListCostAllocationTagsResponse
s {$sel:nextToken:ListCostAllocationTagsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListCostAllocationTagsResponse)

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

instance
  Prelude.NFData
    ListCostAllocationTagsResponse
  where
  rnf :: ListCostAllocationTagsResponse -> ()
rnf ListCostAllocationTagsResponse' {Int
Maybe [CostAllocationTag]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
costAllocationTags :: Maybe [CostAllocationTag]
$sel:httpStatus:ListCostAllocationTagsResponse' :: ListCostAllocationTagsResponse -> Int
$sel:nextToken:ListCostAllocationTagsResponse' :: ListCostAllocationTagsResponse -> Maybe Text
$sel:costAllocationTags:ListCostAllocationTagsResponse' :: ListCostAllocationTagsResponse -> Maybe [CostAllocationTag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [CostAllocationTag]
costAllocationTags
      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 Int
httpStatus