{-# 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.OpenSearch.DescribeOutboundConnections
-- 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 all the outbound cross-cluster connections for a local (source)
-- Amazon OpenSearch Service domain. For more information, see
-- <https://docs.aws.amazon.com/opensearch-service/latest/developerguide/cross-cluster-search.html Cross-cluster search for Amazon OpenSearch Service>.
module Amazonka.OpenSearch.DescribeOutboundConnections
  ( -- * Creating a Request
    DescribeOutboundConnections (..),
    newDescribeOutboundConnections,

    -- * Request Lenses
    describeOutboundConnections_filters,
    describeOutboundConnections_maxResults,
    describeOutboundConnections_nextToken,

    -- * Destructuring the Response
    DescribeOutboundConnectionsResponse (..),
    newDescribeOutboundConnectionsResponse,

    -- * Response Lenses
    describeOutboundConnectionsResponse_connections,
    describeOutboundConnectionsResponse_nextToken,
    describeOutboundConnectionsResponse_httpStatus,
  )
where

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

-- | Container for the parameters to the @DescribeOutboundConnections@
-- operation.
--
-- /See:/ 'newDescribeOutboundConnections' smart constructor.
data DescribeOutboundConnections = DescribeOutboundConnections'
  { -- | List of filter names and values that you can use for requests.
    DescribeOutboundConnections -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | An optional parameter that specifies the maximum number of results to
    -- return. You can use @nextToken@ to get the next page of results.
    DescribeOutboundConnections -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | If your initial @DescribeOutboundConnections@ operation returns a
    -- @nextToken@, you can include the returned @nextToken@ in subsequent
    -- @DescribeOutboundConnections@ operations, which returns results in the
    -- next page.
    DescribeOutboundConnections -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeOutboundConnections -> DescribeOutboundConnections -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeOutboundConnections -> DescribeOutboundConnections -> Bool
$c/= :: DescribeOutboundConnections -> DescribeOutboundConnections -> Bool
== :: DescribeOutboundConnections -> DescribeOutboundConnections -> Bool
$c== :: DescribeOutboundConnections -> DescribeOutboundConnections -> Bool
Prelude.Eq, ReadPrec [DescribeOutboundConnections]
ReadPrec DescribeOutboundConnections
Int -> ReadS DescribeOutboundConnections
ReadS [DescribeOutboundConnections]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeOutboundConnections]
$creadListPrec :: ReadPrec [DescribeOutboundConnections]
readPrec :: ReadPrec DescribeOutboundConnections
$creadPrec :: ReadPrec DescribeOutboundConnections
readList :: ReadS [DescribeOutboundConnections]
$creadList :: ReadS [DescribeOutboundConnections]
readsPrec :: Int -> ReadS DescribeOutboundConnections
$creadsPrec :: Int -> ReadS DescribeOutboundConnections
Prelude.Read, Int -> DescribeOutboundConnections -> ShowS
[DescribeOutboundConnections] -> ShowS
DescribeOutboundConnections -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeOutboundConnections] -> ShowS
$cshowList :: [DescribeOutboundConnections] -> ShowS
show :: DescribeOutboundConnections -> String
$cshow :: DescribeOutboundConnections -> String
showsPrec :: Int -> DescribeOutboundConnections -> ShowS
$cshowsPrec :: Int -> DescribeOutboundConnections -> ShowS
Prelude.Show, forall x.
Rep DescribeOutboundConnections x -> DescribeOutboundConnections
forall x.
DescribeOutboundConnections -> Rep DescribeOutboundConnections x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeOutboundConnections x -> DescribeOutboundConnections
$cfrom :: forall x.
DescribeOutboundConnections -> Rep DescribeOutboundConnections x
Prelude.Generic)

-- |
-- Create a value of 'DescribeOutboundConnections' 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:
--
-- 'filters', 'describeOutboundConnections_filters' - List of filter names and values that you can use for requests.
--
-- 'maxResults', 'describeOutboundConnections_maxResults' - An optional parameter that specifies the maximum number of results to
-- return. You can use @nextToken@ to get the next page of results.
--
-- 'nextToken', 'describeOutboundConnections_nextToken' - If your initial @DescribeOutboundConnections@ operation returns a
-- @nextToken@, you can include the returned @nextToken@ in subsequent
-- @DescribeOutboundConnections@ operations, which returns results in the
-- next page.
newDescribeOutboundConnections ::
  DescribeOutboundConnections
newDescribeOutboundConnections :: DescribeOutboundConnections
newDescribeOutboundConnections =
  DescribeOutboundConnections'
    { $sel:filters:DescribeOutboundConnections' :: Maybe [Filter]
filters =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:DescribeOutboundConnections' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeOutboundConnections' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | List of filter names and values that you can use for requests.
describeOutboundConnections_filters :: Lens.Lens' DescribeOutboundConnections (Prelude.Maybe [Filter])
describeOutboundConnections_filters :: Lens' DescribeOutboundConnections (Maybe [Filter])
describeOutboundConnections_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeOutboundConnections' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: DescribeOutboundConnections
s@DescribeOutboundConnections' {} Maybe [Filter]
a -> DescribeOutboundConnections
s {$sel:filters:DescribeOutboundConnections' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: DescribeOutboundConnections) 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

-- | An optional parameter that specifies the maximum number of results to
-- return. You can use @nextToken@ to get the next page of results.
describeOutboundConnections_maxResults :: Lens.Lens' DescribeOutboundConnections (Prelude.Maybe Prelude.Int)
describeOutboundConnections_maxResults :: Lens' DescribeOutboundConnections (Maybe Int)
describeOutboundConnections_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeOutboundConnections' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: DescribeOutboundConnections
s@DescribeOutboundConnections' {} Maybe Int
a -> DescribeOutboundConnections
s {$sel:maxResults:DescribeOutboundConnections' :: Maybe Int
maxResults = Maybe Int
a} :: DescribeOutboundConnections)

-- | If your initial @DescribeOutboundConnections@ operation returns a
-- @nextToken@, you can include the returned @nextToken@ in subsequent
-- @DescribeOutboundConnections@ operations, which returns results in the
-- next page.
describeOutboundConnections_nextToken :: Lens.Lens' DescribeOutboundConnections (Prelude.Maybe Prelude.Text)
describeOutboundConnections_nextToken :: Lens' DescribeOutboundConnections (Maybe Text)
describeOutboundConnections_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeOutboundConnections' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeOutboundConnections
s@DescribeOutboundConnections' {} Maybe Text
a -> DescribeOutboundConnections
s {$sel:nextToken:DescribeOutboundConnections' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeOutboundConnections)

instance Core.AWSRequest DescribeOutboundConnections where
  type
    AWSResponse DescribeOutboundConnections =
      DescribeOutboundConnectionsResponse
  request :: (Service -> Service)
-> DescribeOutboundConnections
-> Request DescribeOutboundConnections
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 DescribeOutboundConnections
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeOutboundConnections)))
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 [OutboundConnection]
-> Maybe Text -> Int -> DescribeOutboundConnectionsResponse
DescribeOutboundConnectionsResponse'
            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
"Connections" 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 DescribeOutboundConnections where
  hashWithSalt :: Int -> DescribeOutboundConnections -> Int
hashWithSalt Int
_salt DescribeOutboundConnections' {Maybe Int
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:nextToken:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe Text
$sel:maxResults:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe Int
$sel:filters:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe [Filter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Filter]
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData DescribeOutboundConnections where
  rnf :: DescribeOutboundConnections -> ()
rnf DescribeOutboundConnections' {Maybe Int
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:nextToken:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe Text
$sel:maxResults:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe Int
$sel:filters:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe [Filter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Filter]
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

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

instance Data.ToJSON DescribeOutboundConnections where
  toJSON :: DescribeOutboundConnections -> Value
toJSON DescribeOutboundConnections' {Maybe Int
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:nextToken:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe Text
$sel:maxResults:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe Int
$sel:filters:DescribeOutboundConnections' :: DescribeOutboundConnections -> Maybe [Filter]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filters" 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 [Filter]
filters,
            (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 Int
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
          ]
      )

instance Data.ToPath DescribeOutboundConnections where
  toPath :: DescribeOutboundConnections -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/2021-01-01/opensearch/cc/outboundConnection/search"

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

-- | Contains a list of connections matching the filter criteria.
--
-- /See:/ 'newDescribeOutboundConnectionsResponse' smart constructor.
data DescribeOutboundConnectionsResponse = DescribeOutboundConnectionsResponse'
  { -- | List of outbound connections that match the filter criteria.
    DescribeOutboundConnectionsResponse -> Maybe [OutboundConnection]
connections :: Prelude.Maybe [OutboundConnection],
    -- | When @nextToken@ is returned, there are more results available. The
    -- value of @nextToken@ is a unique pagination token for each page. Make
    -- the call again using the returned token to retrieve the next page.
    DescribeOutboundConnectionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeOutboundConnectionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeOutboundConnectionsResponse
-> DescribeOutboundConnectionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeOutboundConnectionsResponse
-> DescribeOutboundConnectionsResponse -> Bool
$c/= :: DescribeOutboundConnectionsResponse
-> DescribeOutboundConnectionsResponse -> Bool
== :: DescribeOutboundConnectionsResponse
-> DescribeOutboundConnectionsResponse -> Bool
$c== :: DescribeOutboundConnectionsResponse
-> DescribeOutboundConnectionsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeOutboundConnectionsResponse]
ReadPrec DescribeOutboundConnectionsResponse
Int -> ReadS DescribeOutboundConnectionsResponse
ReadS [DescribeOutboundConnectionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeOutboundConnectionsResponse]
$creadListPrec :: ReadPrec [DescribeOutboundConnectionsResponse]
readPrec :: ReadPrec DescribeOutboundConnectionsResponse
$creadPrec :: ReadPrec DescribeOutboundConnectionsResponse
readList :: ReadS [DescribeOutboundConnectionsResponse]
$creadList :: ReadS [DescribeOutboundConnectionsResponse]
readsPrec :: Int -> ReadS DescribeOutboundConnectionsResponse
$creadsPrec :: Int -> ReadS DescribeOutboundConnectionsResponse
Prelude.Read, Int -> DescribeOutboundConnectionsResponse -> ShowS
[DescribeOutboundConnectionsResponse] -> ShowS
DescribeOutboundConnectionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeOutboundConnectionsResponse] -> ShowS
$cshowList :: [DescribeOutboundConnectionsResponse] -> ShowS
show :: DescribeOutboundConnectionsResponse -> String
$cshow :: DescribeOutboundConnectionsResponse -> String
showsPrec :: Int -> DescribeOutboundConnectionsResponse -> ShowS
$cshowsPrec :: Int -> DescribeOutboundConnectionsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeOutboundConnectionsResponse x
-> DescribeOutboundConnectionsResponse
forall x.
DescribeOutboundConnectionsResponse
-> Rep DescribeOutboundConnectionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeOutboundConnectionsResponse x
-> DescribeOutboundConnectionsResponse
$cfrom :: forall x.
DescribeOutboundConnectionsResponse
-> Rep DescribeOutboundConnectionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeOutboundConnectionsResponse' 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:
--
-- 'connections', 'describeOutboundConnectionsResponse_connections' - List of outbound connections that match the filter criteria.
--
-- 'nextToken', 'describeOutboundConnectionsResponse_nextToken' - When @nextToken@ is returned, there are more results available. The
-- value of @nextToken@ is a unique pagination token for each page. Make
-- the call again using the returned token to retrieve the next page.
--
-- 'httpStatus', 'describeOutboundConnectionsResponse_httpStatus' - The response's http status code.
newDescribeOutboundConnectionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeOutboundConnectionsResponse
newDescribeOutboundConnectionsResponse :: Int -> DescribeOutboundConnectionsResponse
newDescribeOutboundConnectionsResponse Int
pHttpStatus_ =
  DescribeOutboundConnectionsResponse'
    { $sel:connections:DescribeOutboundConnectionsResponse' :: Maybe [OutboundConnection]
connections =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeOutboundConnectionsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeOutboundConnectionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | List of outbound connections that match the filter criteria.
describeOutboundConnectionsResponse_connections :: Lens.Lens' DescribeOutboundConnectionsResponse (Prelude.Maybe [OutboundConnection])
describeOutboundConnectionsResponse_connections :: Lens'
  DescribeOutboundConnectionsResponse (Maybe [OutboundConnection])
describeOutboundConnectionsResponse_connections = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeOutboundConnectionsResponse' {Maybe [OutboundConnection]
connections :: Maybe [OutboundConnection]
$sel:connections:DescribeOutboundConnectionsResponse' :: DescribeOutboundConnectionsResponse -> Maybe [OutboundConnection]
connections} -> Maybe [OutboundConnection]
connections) (\s :: DescribeOutboundConnectionsResponse
s@DescribeOutboundConnectionsResponse' {} Maybe [OutboundConnection]
a -> DescribeOutboundConnectionsResponse
s {$sel:connections:DescribeOutboundConnectionsResponse' :: Maybe [OutboundConnection]
connections = Maybe [OutboundConnection]
a} :: DescribeOutboundConnectionsResponse) 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 @nextToken@ is returned, there are more results available. The
-- value of @nextToken@ is a unique pagination token for each page. Make
-- the call again using the returned token to retrieve the next page.
describeOutboundConnectionsResponse_nextToken :: Lens.Lens' DescribeOutboundConnectionsResponse (Prelude.Maybe Prelude.Text)
describeOutboundConnectionsResponse_nextToken :: Lens' DescribeOutboundConnectionsResponse (Maybe Text)
describeOutboundConnectionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeOutboundConnectionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeOutboundConnectionsResponse' :: DescribeOutboundConnectionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeOutboundConnectionsResponse
s@DescribeOutboundConnectionsResponse' {} Maybe Text
a -> DescribeOutboundConnectionsResponse
s {$sel:nextToken:DescribeOutboundConnectionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeOutboundConnectionsResponse)

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

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