{-# 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.KMS.ListAliases
-- 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 aliases in the caller\'s Amazon Web Services account and
-- region. For more information about aliases, see CreateAlias.
--
-- By default, the @ListAliases@ operation returns all aliases in the
-- account and region. To get only the aliases associated with a particular
-- KMS key, use the @KeyId@ parameter.
--
-- The @ListAliases@ response can include aliases that you created and
-- associated with your customer managed keys, and aliases that Amazon Web
-- Services created and associated with Amazon Web Services managed keys in
-- your account. You can recognize Amazon Web Services aliases because
-- their names have the format @aws\/\<service-name>@, such as
-- @aws\/dynamodb@.
--
-- The response might also include aliases that have no @TargetKeyId@
-- field. These are predefined aliases that Amazon Web Services has created
-- but has not yet associated with a KMS key. Aliases that Amazon Web
-- Services creates in your account, including predefined aliases, do not
-- count against your
-- <https://docs.aws.amazon.com/kms/latest/developerguide/limits.html#aliases-limit KMS aliases quota>.
--
-- __Cross-account use__: No. @ListAliases@ does not return aliases in
-- other Amazon Web Services accounts.
--
-- __Required permissions__:
-- <https://docs.aws.amazon.com/kms/latest/developerguide/kms-api-permissions-reference.html kms:ListAliases>
-- (IAM policy)
--
-- For details, see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/kms-alias.html#alias-access Controlling access to aliases>
-- in the /Key Management Service Developer Guide/.
--
-- __Related operations:__
--
-- -   CreateAlias
--
-- -   DeleteAlias
--
-- -   UpdateAlias
--
-- This operation returns paginated results.
module Amazonka.KMS.ListAliases
  ( -- * Creating a Request
    ListAliases (..),
    newListAliases,

    -- * Request Lenses
    listAliases_keyId,
    listAliases_limit,
    listAliases_marker,

    -- * Destructuring the Response
    ListAliasesResponse (..),
    newListAliasesResponse,

    -- * Response Lenses
    listAliasesResponse_aliases,
    listAliasesResponse_nextMarker,
    listAliasesResponse_truncated,
    listAliasesResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.KMS.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListAliases' smart constructor.
data ListAliases = ListAliases'
  { -- | Lists only aliases that are associated with the specified KMS key. Enter
    -- a KMS key in your Amazon Web Services account.
    --
    -- This parameter is optional. If you omit it, @ListAliases@ returns all
    -- aliases in the account and Region.
    --
    -- Specify the key ID or key ARN of the KMS key.
    --
    -- For example:
    --
    -- -   Key ID: @1234abcd-12ab-34cd-56ef-1234567890ab@
    --
    -- -   Key ARN:
    --     @arn:aws:kms:us-east-2:111122223333:key\/1234abcd-12ab-34cd-56ef-1234567890ab@
    --
    -- To get the key ID and key ARN for a KMS key, use ListKeys or
    -- DescribeKey.
    ListAliases -> Maybe Text
keyId :: Prelude.Maybe Prelude.Text,
    -- | Use this parameter to specify the maximum number of items to return.
    -- When this value is present, KMS does not return more than the specified
    -- number of items, but it might return fewer.
    --
    -- This value is optional. If you include a value, it must be between 1 and
    -- 100, inclusive. If you do not include a value, it defaults to 50.
    ListAliases -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | Use this parameter in a subsequent request after you receive a response
    -- with truncated results. Set it to the value of @NextMarker@ from the
    -- truncated response you just received.
    ListAliases -> Maybe Text
marker :: Prelude.Maybe Prelude.Text
  }
  deriving (ListAliases -> ListAliases -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAliases -> ListAliases -> Bool
$c/= :: ListAliases -> ListAliases -> Bool
== :: ListAliases -> ListAliases -> Bool
$c== :: ListAliases -> ListAliases -> Bool
Prelude.Eq, ReadPrec [ListAliases]
ReadPrec ListAliases
Int -> ReadS ListAliases
ReadS [ListAliases]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAliases]
$creadListPrec :: ReadPrec [ListAliases]
readPrec :: ReadPrec ListAliases
$creadPrec :: ReadPrec ListAliases
readList :: ReadS [ListAliases]
$creadList :: ReadS [ListAliases]
readsPrec :: Int -> ReadS ListAliases
$creadsPrec :: Int -> ReadS ListAliases
Prelude.Read, Int -> ListAliases -> ShowS
[ListAliases] -> ShowS
ListAliases -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAliases] -> ShowS
$cshowList :: [ListAliases] -> ShowS
show :: ListAliases -> String
$cshow :: ListAliases -> String
showsPrec :: Int -> ListAliases -> ShowS
$cshowsPrec :: Int -> ListAliases -> ShowS
Prelude.Show, forall x. Rep ListAliases x -> ListAliases
forall x. ListAliases -> Rep ListAliases x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAliases x -> ListAliases
$cfrom :: forall x. ListAliases -> Rep ListAliases x
Prelude.Generic)

-- |
-- Create a value of 'ListAliases' 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:
--
-- 'keyId', 'listAliases_keyId' - Lists only aliases that are associated with the specified KMS key. Enter
-- a KMS key in your Amazon Web Services account.
--
-- This parameter is optional. If you omit it, @ListAliases@ returns all
-- aliases in the account and Region.
--
-- Specify the key ID or key ARN of the KMS key.
--
-- For example:
--
-- -   Key ID: @1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- -   Key ARN:
--     @arn:aws:kms:us-east-2:111122223333:key\/1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- To get the key ID and key ARN for a KMS key, use ListKeys or
-- DescribeKey.
--
-- 'limit', 'listAliases_limit' - Use this parameter to specify the maximum number of items to return.
-- When this value is present, KMS does not return more than the specified
-- number of items, but it might return fewer.
--
-- This value is optional. If you include a value, it must be between 1 and
-- 100, inclusive. If you do not include a value, it defaults to 50.
--
-- 'marker', 'listAliases_marker' - Use this parameter in a subsequent request after you receive a response
-- with truncated results. Set it to the value of @NextMarker@ from the
-- truncated response you just received.
newListAliases ::
  ListAliases
newListAliases :: ListAliases
newListAliases =
  ListAliases'
    { $sel:keyId:ListAliases' :: Maybe Text
keyId = forall a. Maybe a
Prelude.Nothing,
      $sel:limit:ListAliases' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:ListAliases' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing
    }

-- | Lists only aliases that are associated with the specified KMS key. Enter
-- a KMS key in your Amazon Web Services account.
--
-- This parameter is optional. If you omit it, @ListAliases@ returns all
-- aliases in the account and Region.
--
-- Specify the key ID or key ARN of the KMS key.
--
-- For example:
--
-- -   Key ID: @1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- -   Key ARN:
--     @arn:aws:kms:us-east-2:111122223333:key\/1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- To get the key ID and key ARN for a KMS key, use ListKeys or
-- DescribeKey.
listAliases_keyId :: Lens.Lens' ListAliases (Prelude.Maybe Prelude.Text)
listAliases_keyId :: Lens' ListAliases (Maybe Text)
listAliases_keyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAliases' {Maybe Text
keyId :: Maybe Text
$sel:keyId:ListAliases' :: ListAliases -> Maybe Text
keyId} -> Maybe Text
keyId) (\s :: ListAliases
s@ListAliases' {} Maybe Text
a -> ListAliases
s {$sel:keyId:ListAliases' :: Maybe Text
keyId = Maybe Text
a} :: ListAliases)

-- | Use this parameter to specify the maximum number of items to return.
-- When this value is present, KMS does not return more than the specified
-- number of items, but it might return fewer.
--
-- This value is optional. If you include a value, it must be between 1 and
-- 100, inclusive. If you do not include a value, it defaults to 50.
listAliases_limit :: Lens.Lens' ListAliases (Prelude.Maybe Prelude.Natural)
listAliases_limit :: Lens' ListAliases (Maybe Natural)
listAliases_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAliases' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListAliases' :: ListAliases -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListAliases
s@ListAliases' {} Maybe Natural
a -> ListAliases
s {$sel:limit:ListAliases' :: Maybe Natural
limit = Maybe Natural
a} :: ListAliases)

-- | Use this parameter in a subsequent request after you receive a response
-- with truncated results. Set it to the value of @NextMarker@ from the
-- truncated response you just received.
listAliases_marker :: Lens.Lens' ListAliases (Prelude.Maybe Prelude.Text)
listAliases_marker :: Lens' ListAliases (Maybe Text)
listAliases_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAliases' {Maybe Text
marker :: Maybe Text
$sel:marker:ListAliases' :: ListAliases -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListAliases
s@ListAliases' {} Maybe Text
a -> ListAliases
s {$sel:marker:ListAliases' :: Maybe Text
marker = Maybe Text
a} :: ListAliases)

instance Core.AWSPager ListAliases where
  page :: ListAliases -> AWSResponse ListAliases -> Maybe ListAliases
page ListAliases
rq AWSResponse ListAliases
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListAliases
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAliasesResponse (Maybe Bool)
listAliasesResponse_truncated
            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. Maybe a -> Bool
Prelude.isNothing
        ( AWSResponse ListAliases
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAliasesResponse (Maybe Text)
listAliasesResponse_nextMarker
            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
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListAliases
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListAliases (Maybe Text)
listAliases_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListAliases
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAliasesResponse (Maybe Text)
listAliasesResponse_nextMarker
          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 ListAliases where
  type AWSResponse ListAliases = ListAliasesResponse
  request :: (Service -> Service) -> ListAliases -> Request ListAliases
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 ListAliases
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListAliases)))
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 [AliasListEntry]
-> Maybe Text -> Maybe Bool -> Int -> ListAliasesResponse
ListAliasesResponse'
            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
"Aliases" 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
"NextMarker")
            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
"Truncated")
            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 ListAliases where
  hashWithSalt :: Int -> ListAliases -> Int
hashWithSalt Int
_salt ListAliases' {Maybe Natural
Maybe Text
marker :: Maybe Text
limit :: Maybe Natural
keyId :: Maybe Text
$sel:marker:ListAliases' :: ListAliases -> Maybe Text
$sel:limit:ListAliases' :: ListAliases -> Maybe Natural
$sel:keyId:ListAliases' :: ListAliases -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
keyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker

instance Prelude.NFData ListAliases where
  rnf :: ListAliases -> ()
rnf ListAliases' {Maybe Natural
Maybe Text
marker :: Maybe Text
limit :: Maybe Natural
keyId :: Maybe Text
$sel:marker:ListAliases' :: ListAliases -> Maybe Text
$sel:limit:ListAliases' :: ListAliases -> Maybe Natural
$sel:keyId:ListAliases' :: ListAliases -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
keyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker

instance Data.ToHeaders ListAliases where
  toHeaders :: ListAliases -> 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
"TrentService.ListAliases" :: 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 ListAliases where
  toJSON :: ListAliases -> Value
toJSON ListAliases' {Maybe Natural
Maybe Text
marker :: Maybe Text
limit :: Maybe Natural
keyId :: Maybe Text
$sel:marker:ListAliases' :: ListAliases -> Maybe Text
$sel:limit:ListAliases' :: ListAliases -> Maybe Natural
$sel:keyId:ListAliases' :: ListAliases -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"KeyId" 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
keyId,
            (Key
"Limit" 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
limit,
            (Key
"Marker" 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
marker
          ]
      )

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

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

-- | /See:/ 'newListAliasesResponse' smart constructor.
data ListAliasesResponse = ListAliasesResponse'
  { -- | A list of aliases.
    ListAliasesResponse -> Maybe [AliasListEntry]
aliases :: Prelude.Maybe [AliasListEntry],
    -- | When @Truncated@ is true, this element is present and contains the value
    -- to use for the @Marker@ parameter in a subsequent request.
    ListAliasesResponse -> Maybe Text
nextMarker :: Prelude.Maybe Prelude.Text,
    -- | A flag that indicates whether there are more items in the list. When
    -- this value is true, the list in this response is truncated. To get more
    -- items, pass the value of the @NextMarker@ element in thisresponse to the
    -- @Marker@ parameter in a subsequent request.
    ListAliasesResponse -> Maybe Bool
truncated :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    ListAliasesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListAliasesResponse -> ListAliasesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAliasesResponse -> ListAliasesResponse -> Bool
$c/= :: ListAliasesResponse -> ListAliasesResponse -> Bool
== :: ListAliasesResponse -> ListAliasesResponse -> Bool
$c== :: ListAliasesResponse -> ListAliasesResponse -> Bool
Prelude.Eq, ReadPrec [ListAliasesResponse]
ReadPrec ListAliasesResponse
Int -> ReadS ListAliasesResponse
ReadS [ListAliasesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAliasesResponse]
$creadListPrec :: ReadPrec [ListAliasesResponse]
readPrec :: ReadPrec ListAliasesResponse
$creadPrec :: ReadPrec ListAliasesResponse
readList :: ReadS [ListAliasesResponse]
$creadList :: ReadS [ListAliasesResponse]
readsPrec :: Int -> ReadS ListAliasesResponse
$creadsPrec :: Int -> ReadS ListAliasesResponse
Prelude.Read, Int -> ListAliasesResponse -> ShowS
[ListAliasesResponse] -> ShowS
ListAliasesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAliasesResponse] -> ShowS
$cshowList :: [ListAliasesResponse] -> ShowS
show :: ListAliasesResponse -> String
$cshow :: ListAliasesResponse -> String
showsPrec :: Int -> ListAliasesResponse -> ShowS
$cshowsPrec :: Int -> ListAliasesResponse -> ShowS
Prelude.Show, forall x. Rep ListAliasesResponse x -> ListAliasesResponse
forall x. ListAliasesResponse -> Rep ListAliasesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAliasesResponse x -> ListAliasesResponse
$cfrom :: forall x. ListAliasesResponse -> Rep ListAliasesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAliasesResponse' 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:
--
-- 'aliases', 'listAliasesResponse_aliases' - A list of aliases.
--
-- 'nextMarker', 'listAliasesResponse_nextMarker' - When @Truncated@ is true, this element is present and contains the value
-- to use for the @Marker@ parameter in a subsequent request.
--
-- 'truncated', 'listAliasesResponse_truncated' - A flag that indicates whether there are more items in the list. When
-- this value is true, the list in this response is truncated. To get more
-- items, pass the value of the @NextMarker@ element in thisresponse to the
-- @Marker@ parameter in a subsequent request.
--
-- 'httpStatus', 'listAliasesResponse_httpStatus' - The response's http status code.
newListAliasesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAliasesResponse
newListAliasesResponse :: Int -> ListAliasesResponse
newListAliasesResponse Int
pHttpStatus_ =
  ListAliasesResponse'
    { $sel:aliases:ListAliasesResponse' :: Maybe [AliasListEntry]
aliases = forall a. Maybe a
Prelude.Nothing,
      $sel:nextMarker:ListAliasesResponse' :: Maybe Text
nextMarker = forall a. Maybe a
Prelude.Nothing,
      $sel:truncated:ListAliasesResponse' :: Maybe Bool
truncated = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAliasesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of aliases.
listAliasesResponse_aliases :: Lens.Lens' ListAliasesResponse (Prelude.Maybe [AliasListEntry])
listAliasesResponse_aliases :: Lens' ListAliasesResponse (Maybe [AliasListEntry])
listAliasesResponse_aliases = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAliasesResponse' {Maybe [AliasListEntry]
aliases :: Maybe [AliasListEntry]
$sel:aliases:ListAliasesResponse' :: ListAliasesResponse -> Maybe [AliasListEntry]
aliases} -> Maybe [AliasListEntry]
aliases) (\s :: ListAliasesResponse
s@ListAliasesResponse' {} Maybe [AliasListEntry]
a -> ListAliasesResponse
s {$sel:aliases:ListAliasesResponse' :: Maybe [AliasListEntry]
aliases = Maybe [AliasListEntry]
a} :: ListAliasesResponse) 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

-- | When @Truncated@ is true, this element is present and contains the value
-- to use for the @Marker@ parameter in a subsequent request.
listAliasesResponse_nextMarker :: Lens.Lens' ListAliasesResponse (Prelude.Maybe Prelude.Text)
listAliasesResponse_nextMarker :: Lens' ListAliasesResponse (Maybe Text)
listAliasesResponse_nextMarker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAliasesResponse' {Maybe Text
nextMarker :: Maybe Text
$sel:nextMarker:ListAliasesResponse' :: ListAliasesResponse -> Maybe Text
nextMarker} -> Maybe Text
nextMarker) (\s :: ListAliasesResponse
s@ListAliasesResponse' {} Maybe Text
a -> ListAliasesResponse
s {$sel:nextMarker:ListAliasesResponse' :: Maybe Text
nextMarker = Maybe Text
a} :: ListAliasesResponse)

-- | A flag that indicates whether there are more items in the list. When
-- this value is true, the list in this response is truncated. To get more
-- items, pass the value of the @NextMarker@ element in thisresponse to the
-- @Marker@ parameter in a subsequent request.
listAliasesResponse_truncated :: Lens.Lens' ListAliasesResponse (Prelude.Maybe Prelude.Bool)
listAliasesResponse_truncated :: Lens' ListAliasesResponse (Maybe Bool)
listAliasesResponse_truncated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAliasesResponse' {Maybe Bool
truncated :: Maybe Bool
$sel:truncated:ListAliasesResponse' :: ListAliasesResponse -> Maybe Bool
truncated} -> Maybe Bool
truncated) (\s :: ListAliasesResponse
s@ListAliasesResponse' {} Maybe Bool
a -> ListAliasesResponse
s {$sel:truncated:ListAliasesResponse' :: Maybe Bool
truncated = Maybe Bool
a} :: ListAliasesResponse)

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

instance Prelude.NFData ListAliasesResponse where
  rnf :: ListAliasesResponse -> ()
rnf ListAliasesResponse' {Int
Maybe Bool
Maybe [AliasListEntry]
Maybe Text
httpStatus :: Int
truncated :: Maybe Bool
nextMarker :: Maybe Text
aliases :: Maybe [AliasListEntry]
$sel:httpStatus:ListAliasesResponse' :: ListAliasesResponse -> Int
$sel:truncated:ListAliasesResponse' :: ListAliasesResponse -> Maybe Bool
$sel:nextMarker:ListAliasesResponse' :: ListAliasesResponse -> Maybe Text
$sel:aliases:ListAliasesResponse' :: ListAliasesResponse -> Maybe [AliasListEntry]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AliasListEntry]
aliases
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextMarker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
truncated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus