{-# 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.CloudWatchEvents.ListApiDestinations
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves a list of API destination in the account in the current
-- Region.
module Amazonka.CloudWatchEvents.ListApiDestinations
  ( -- * Creating a Request
    ListApiDestinations (..),
    newListApiDestinations,

    -- * Request Lenses
    listApiDestinations_connectionArn,
    listApiDestinations_limit,
    listApiDestinations_namePrefix,
    listApiDestinations_nextToken,

    -- * Destructuring the Response
    ListApiDestinationsResponse (..),
    newListApiDestinationsResponse,

    -- * Response Lenses
    listApiDestinationsResponse_apiDestinations,
    listApiDestinationsResponse_nextToken,
    listApiDestinationsResponse_httpStatus,
  )
where

import Amazonka.CloudWatchEvents.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:/ 'newListApiDestinations' smart constructor.
data ListApiDestinations = ListApiDestinations'
  { -- | The ARN of the connection specified for the API destination.
    ListApiDestinations -> Maybe Text
connectionArn :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of API destinations to include in the response.
    ListApiDestinations -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | A name prefix to filter results returned. Only API destinations with a
    -- name that starts with the prefix are returned.
    ListApiDestinations -> Maybe Text
namePrefix :: Prelude.Maybe Prelude.Text,
    -- | The token returned by a previous call to retrieve the next set of
    -- results.
    ListApiDestinations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListApiDestinations -> ListApiDestinations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApiDestinations -> ListApiDestinations -> Bool
$c/= :: ListApiDestinations -> ListApiDestinations -> Bool
== :: ListApiDestinations -> ListApiDestinations -> Bool
$c== :: ListApiDestinations -> ListApiDestinations -> Bool
Prelude.Eq, ReadPrec [ListApiDestinations]
ReadPrec ListApiDestinations
Int -> ReadS ListApiDestinations
ReadS [ListApiDestinations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApiDestinations]
$creadListPrec :: ReadPrec [ListApiDestinations]
readPrec :: ReadPrec ListApiDestinations
$creadPrec :: ReadPrec ListApiDestinations
readList :: ReadS [ListApiDestinations]
$creadList :: ReadS [ListApiDestinations]
readsPrec :: Int -> ReadS ListApiDestinations
$creadsPrec :: Int -> ReadS ListApiDestinations
Prelude.Read, Int -> ListApiDestinations -> ShowS
[ListApiDestinations] -> ShowS
ListApiDestinations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApiDestinations] -> ShowS
$cshowList :: [ListApiDestinations] -> ShowS
show :: ListApiDestinations -> String
$cshow :: ListApiDestinations -> String
showsPrec :: Int -> ListApiDestinations -> ShowS
$cshowsPrec :: Int -> ListApiDestinations -> ShowS
Prelude.Show, forall x. Rep ListApiDestinations x -> ListApiDestinations
forall x. ListApiDestinations -> Rep ListApiDestinations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListApiDestinations x -> ListApiDestinations
$cfrom :: forall x. ListApiDestinations -> Rep ListApiDestinations x
Prelude.Generic)

-- |
-- Create a value of 'ListApiDestinations' 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:
--
-- 'connectionArn', 'listApiDestinations_connectionArn' - The ARN of the connection specified for the API destination.
--
-- 'limit', 'listApiDestinations_limit' - The maximum number of API destinations to include in the response.
--
-- 'namePrefix', 'listApiDestinations_namePrefix' - A name prefix to filter results returned. Only API destinations with a
-- name that starts with the prefix are returned.
--
-- 'nextToken', 'listApiDestinations_nextToken' - The token returned by a previous call to retrieve the next set of
-- results.
newListApiDestinations ::
  ListApiDestinations
newListApiDestinations :: ListApiDestinations
newListApiDestinations =
  ListApiDestinations'
    { $sel:connectionArn:ListApiDestinations' :: Maybe Text
connectionArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:limit:ListApiDestinations' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:namePrefix:ListApiDestinations' :: Maybe Text
namePrefix = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListApiDestinations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The ARN of the connection specified for the API destination.
listApiDestinations_connectionArn :: Lens.Lens' ListApiDestinations (Prelude.Maybe Prelude.Text)
listApiDestinations_connectionArn :: Lens' ListApiDestinations (Maybe Text)
listApiDestinations_connectionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApiDestinations' {Maybe Text
connectionArn :: Maybe Text
$sel:connectionArn:ListApiDestinations' :: ListApiDestinations -> Maybe Text
connectionArn} -> Maybe Text
connectionArn) (\s :: ListApiDestinations
s@ListApiDestinations' {} Maybe Text
a -> ListApiDestinations
s {$sel:connectionArn:ListApiDestinations' :: Maybe Text
connectionArn = Maybe Text
a} :: ListApiDestinations)

-- | The maximum number of API destinations to include in the response.
listApiDestinations_limit :: Lens.Lens' ListApiDestinations (Prelude.Maybe Prelude.Natural)
listApiDestinations_limit :: Lens' ListApiDestinations (Maybe Natural)
listApiDestinations_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApiDestinations' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListApiDestinations' :: ListApiDestinations -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListApiDestinations
s@ListApiDestinations' {} Maybe Natural
a -> ListApiDestinations
s {$sel:limit:ListApiDestinations' :: Maybe Natural
limit = Maybe Natural
a} :: ListApiDestinations)

-- | A name prefix to filter results returned. Only API destinations with a
-- name that starts with the prefix are returned.
listApiDestinations_namePrefix :: Lens.Lens' ListApiDestinations (Prelude.Maybe Prelude.Text)
listApiDestinations_namePrefix :: Lens' ListApiDestinations (Maybe Text)
listApiDestinations_namePrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApiDestinations' {Maybe Text
namePrefix :: Maybe Text
$sel:namePrefix:ListApiDestinations' :: ListApiDestinations -> Maybe Text
namePrefix} -> Maybe Text
namePrefix) (\s :: ListApiDestinations
s@ListApiDestinations' {} Maybe Text
a -> ListApiDestinations
s {$sel:namePrefix:ListApiDestinations' :: Maybe Text
namePrefix = Maybe Text
a} :: ListApiDestinations)

-- | The token returned by a previous call to retrieve the next set of
-- results.
listApiDestinations_nextToken :: Lens.Lens' ListApiDestinations (Prelude.Maybe Prelude.Text)
listApiDestinations_nextToken :: Lens' ListApiDestinations (Maybe Text)
listApiDestinations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApiDestinations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApiDestinations' :: ListApiDestinations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApiDestinations
s@ListApiDestinations' {} Maybe Text
a -> ListApiDestinations
s {$sel:nextToken:ListApiDestinations' :: Maybe Text
nextToken = Maybe Text
a} :: ListApiDestinations)

instance Core.AWSRequest ListApiDestinations where
  type
    AWSResponse ListApiDestinations =
      ListApiDestinationsResponse
  request :: (Service -> Service)
-> ListApiDestinations -> Request ListApiDestinations
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 ListApiDestinations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListApiDestinations)))
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 [ApiDestination]
-> Maybe Text -> Int -> ListApiDestinationsResponse
ListApiDestinationsResponse'
            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
"ApiDestinations"
                            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 ListApiDestinations where
  hashWithSalt :: Int -> ListApiDestinations -> Int
hashWithSalt Int
_salt ListApiDestinations' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
namePrefix :: Maybe Text
limit :: Maybe Natural
connectionArn :: Maybe Text
$sel:nextToken:ListApiDestinations' :: ListApiDestinations -> Maybe Text
$sel:namePrefix:ListApiDestinations' :: ListApiDestinations -> Maybe Text
$sel:limit:ListApiDestinations' :: ListApiDestinations -> Maybe Natural
$sel:connectionArn:ListApiDestinations' :: ListApiDestinations -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectionArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
namePrefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListApiDestinations where
  rnf :: ListApiDestinations -> ()
rnf ListApiDestinations' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
namePrefix :: Maybe Text
limit :: Maybe Natural
connectionArn :: Maybe Text
$sel:nextToken:ListApiDestinations' :: ListApiDestinations -> Maybe Text
$sel:namePrefix:ListApiDestinations' :: ListApiDestinations -> Maybe Text
$sel:limit:ListApiDestinations' :: ListApiDestinations -> Maybe Natural
$sel:connectionArn:ListApiDestinations' :: ListApiDestinations -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectionArn
      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
namePrefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders ListApiDestinations where
  toHeaders :: ListApiDestinations -> 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
"AWSEvents.ListApiDestinations" ::
                          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 ListApiDestinations where
  toJSON :: ListApiDestinations -> Value
toJSON ListApiDestinations' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
namePrefix :: Maybe Text
limit :: Maybe Natural
connectionArn :: Maybe Text
$sel:nextToken:ListApiDestinations' :: ListApiDestinations -> Maybe Text
$sel:namePrefix:ListApiDestinations' :: ListApiDestinations -> Maybe Text
$sel:limit:ListApiDestinations' :: ListApiDestinations -> Maybe Natural
$sel:connectionArn:ListApiDestinations' :: ListApiDestinations -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ConnectionArn" 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
connectionArn,
            (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
"NamePrefix" 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
namePrefix,
            (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
          ]
      )

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

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

-- | /See:/ 'newListApiDestinationsResponse' smart constructor.
data ListApiDestinationsResponse = ListApiDestinationsResponse'
  { -- | An array of @ApiDestination@ objects that include information about an
    -- API destination.
    ListApiDestinationsResponse -> Maybe [ApiDestination]
apiDestinations :: Prelude.Maybe [ApiDestination],
    -- | A token you can use in a subsequent request to retrieve the next set of
    -- results.
    ListApiDestinationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListApiDestinationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListApiDestinationsResponse -> ListApiDestinationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApiDestinationsResponse -> ListApiDestinationsResponse -> Bool
$c/= :: ListApiDestinationsResponse -> ListApiDestinationsResponse -> Bool
== :: ListApiDestinationsResponse -> ListApiDestinationsResponse -> Bool
$c== :: ListApiDestinationsResponse -> ListApiDestinationsResponse -> Bool
Prelude.Eq, ReadPrec [ListApiDestinationsResponse]
ReadPrec ListApiDestinationsResponse
Int -> ReadS ListApiDestinationsResponse
ReadS [ListApiDestinationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApiDestinationsResponse]
$creadListPrec :: ReadPrec [ListApiDestinationsResponse]
readPrec :: ReadPrec ListApiDestinationsResponse
$creadPrec :: ReadPrec ListApiDestinationsResponse
readList :: ReadS [ListApiDestinationsResponse]
$creadList :: ReadS [ListApiDestinationsResponse]
readsPrec :: Int -> ReadS ListApiDestinationsResponse
$creadsPrec :: Int -> ReadS ListApiDestinationsResponse
Prelude.Read, Int -> ListApiDestinationsResponse -> ShowS
[ListApiDestinationsResponse] -> ShowS
ListApiDestinationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApiDestinationsResponse] -> ShowS
$cshowList :: [ListApiDestinationsResponse] -> ShowS
show :: ListApiDestinationsResponse -> String
$cshow :: ListApiDestinationsResponse -> String
showsPrec :: Int -> ListApiDestinationsResponse -> ShowS
$cshowsPrec :: Int -> ListApiDestinationsResponse -> ShowS
Prelude.Show, forall x.
Rep ListApiDestinationsResponse x -> ListApiDestinationsResponse
forall x.
ListApiDestinationsResponse -> Rep ListApiDestinationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApiDestinationsResponse x -> ListApiDestinationsResponse
$cfrom :: forall x.
ListApiDestinationsResponse -> Rep ListApiDestinationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListApiDestinationsResponse' 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:
--
-- 'apiDestinations', 'listApiDestinationsResponse_apiDestinations' - An array of @ApiDestination@ objects that include information about an
-- API destination.
--
-- 'nextToken', 'listApiDestinationsResponse_nextToken' - A token you can use in a subsequent request to retrieve the next set of
-- results.
--
-- 'httpStatus', 'listApiDestinationsResponse_httpStatus' - The response's http status code.
newListApiDestinationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListApiDestinationsResponse
newListApiDestinationsResponse :: Int -> ListApiDestinationsResponse
newListApiDestinationsResponse Int
pHttpStatus_ =
  ListApiDestinationsResponse'
    { $sel:apiDestinations:ListApiDestinationsResponse' :: Maybe [ApiDestination]
apiDestinations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListApiDestinationsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListApiDestinationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of @ApiDestination@ objects that include information about an
-- API destination.
listApiDestinationsResponse_apiDestinations :: Lens.Lens' ListApiDestinationsResponse (Prelude.Maybe [ApiDestination])
listApiDestinationsResponse_apiDestinations :: Lens' ListApiDestinationsResponse (Maybe [ApiDestination])
listApiDestinationsResponse_apiDestinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApiDestinationsResponse' {Maybe [ApiDestination]
apiDestinations :: Maybe [ApiDestination]
$sel:apiDestinations:ListApiDestinationsResponse' :: ListApiDestinationsResponse -> Maybe [ApiDestination]
apiDestinations} -> Maybe [ApiDestination]
apiDestinations) (\s :: ListApiDestinationsResponse
s@ListApiDestinationsResponse' {} Maybe [ApiDestination]
a -> ListApiDestinationsResponse
s {$sel:apiDestinations:ListApiDestinationsResponse' :: Maybe [ApiDestination]
apiDestinations = Maybe [ApiDestination]
a} :: ListApiDestinationsResponse) 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

-- | A token you can use in a subsequent request to retrieve the next set of
-- results.
listApiDestinationsResponse_nextToken :: Lens.Lens' ListApiDestinationsResponse (Prelude.Maybe Prelude.Text)
listApiDestinationsResponse_nextToken :: Lens' ListApiDestinationsResponse (Maybe Text)
listApiDestinationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApiDestinationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApiDestinationsResponse' :: ListApiDestinationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApiDestinationsResponse
s@ListApiDestinationsResponse' {} Maybe Text
a -> ListApiDestinationsResponse
s {$sel:nextToken:ListApiDestinationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListApiDestinationsResponse)

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

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