{-# 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.DMS.DescribeConnections
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the status of the connections that have been made between the
-- replication instance and an endpoint. Connections are created when you
-- test an endpoint.
--
-- This operation returns paginated results.
module Amazonka.DMS.DescribeConnections
  ( -- * Creating a Request
    DescribeConnections (..),
    newDescribeConnections,

    -- * Request Lenses
    describeConnections_filters,
    describeConnections_marker,
    describeConnections_maxRecords,

    -- * Destructuring the Response
    DescribeConnectionsResponse (..),
    newDescribeConnectionsResponse,

    -- * Response Lenses
    describeConnectionsResponse_connections,
    describeConnectionsResponse_marker,
    describeConnectionsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.DMS.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:/ 'newDescribeConnections' smart constructor.
data DescribeConnections = DescribeConnections'
  { -- | The filters applied to the connection.
    --
    -- Valid filter names: endpoint-arn | replication-instance-arn
    DescribeConnections -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | An optional pagination token provided by a previous request. If this
    -- parameter is specified, the response includes only records beyond the
    -- marker, up to the value specified by @MaxRecords@.
    DescribeConnections -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of records to include in the response. If more
    -- records exist than the specified @MaxRecords@ value, a pagination token
    -- called a marker is included in the response so that the remaining
    -- results can be retrieved.
    --
    -- Default: 100
    --
    -- Constraints: Minimum 20, maximum 100.
    DescribeConnections -> Maybe Int
maxRecords :: Prelude.Maybe Prelude.Int
  }
  deriving (DescribeConnections -> DescribeConnections -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConnections -> DescribeConnections -> Bool
$c/= :: DescribeConnections -> DescribeConnections -> Bool
== :: DescribeConnections -> DescribeConnections -> Bool
$c== :: DescribeConnections -> DescribeConnections -> Bool
Prelude.Eq, ReadPrec [DescribeConnections]
ReadPrec DescribeConnections
Int -> ReadS DescribeConnections
ReadS [DescribeConnections]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConnections]
$creadListPrec :: ReadPrec [DescribeConnections]
readPrec :: ReadPrec DescribeConnections
$creadPrec :: ReadPrec DescribeConnections
readList :: ReadS [DescribeConnections]
$creadList :: ReadS [DescribeConnections]
readsPrec :: Int -> ReadS DescribeConnections
$creadsPrec :: Int -> ReadS DescribeConnections
Prelude.Read, Int -> DescribeConnections -> ShowS
[DescribeConnections] -> ShowS
DescribeConnections -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConnections] -> ShowS
$cshowList :: [DescribeConnections] -> ShowS
show :: DescribeConnections -> String
$cshow :: DescribeConnections -> String
showsPrec :: Int -> DescribeConnections -> ShowS
$cshowsPrec :: Int -> DescribeConnections -> ShowS
Prelude.Show, forall x. Rep DescribeConnections x -> DescribeConnections
forall x. DescribeConnections -> Rep DescribeConnections x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeConnections x -> DescribeConnections
$cfrom :: forall x. DescribeConnections -> Rep DescribeConnections x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConnections' 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', 'describeConnections_filters' - The filters applied to the connection.
--
-- Valid filter names: endpoint-arn | replication-instance-arn
--
-- 'marker', 'describeConnections_marker' - An optional pagination token provided by a previous request. If this
-- parameter is specified, the response includes only records beyond the
-- marker, up to the value specified by @MaxRecords@.
--
-- 'maxRecords', 'describeConnections_maxRecords' - The maximum number of records to include in the response. If more
-- records exist than the specified @MaxRecords@ value, a pagination token
-- called a marker is included in the response so that the remaining
-- results can be retrieved.
--
-- Default: 100
--
-- Constraints: Minimum 20, maximum 100.
newDescribeConnections ::
  DescribeConnections
newDescribeConnections :: DescribeConnections
newDescribeConnections =
  DescribeConnections'
    { $sel:filters:DescribeConnections' :: Maybe [Filter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:DescribeConnections' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRecords:DescribeConnections' :: Maybe Int
maxRecords = forall a. Maybe a
Prelude.Nothing
    }

-- | The filters applied to the connection.
--
-- Valid filter names: endpoint-arn | replication-instance-arn
describeConnections_filters :: Lens.Lens' DescribeConnections (Prelude.Maybe [Filter])
describeConnections_filters :: Lens' DescribeConnections (Maybe [Filter])
describeConnections_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnections' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:DescribeConnections' :: DescribeConnections -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: DescribeConnections
s@DescribeConnections' {} Maybe [Filter]
a -> DescribeConnections
s {$sel:filters:DescribeConnections' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: DescribeConnections) 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 pagination token provided by a previous request. If this
-- parameter is specified, the response includes only records beyond the
-- marker, up to the value specified by @MaxRecords@.
describeConnections_marker :: Lens.Lens' DescribeConnections (Prelude.Maybe Prelude.Text)
describeConnections_marker :: Lens' DescribeConnections (Maybe Text)
describeConnections_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnections' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeConnections' :: DescribeConnections -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeConnections
s@DescribeConnections' {} Maybe Text
a -> DescribeConnections
s {$sel:marker:DescribeConnections' :: Maybe Text
marker = Maybe Text
a} :: DescribeConnections)

-- | The maximum number of records to include in the response. If more
-- records exist than the specified @MaxRecords@ value, a pagination token
-- called a marker is included in the response so that the remaining
-- results can be retrieved.
--
-- Default: 100
--
-- Constraints: Minimum 20, maximum 100.
describeConnections_maxRecords :: Lens.Lens' DescribeConnections (Prelude.Maybe Prelude.Int)
describeConnections_maxRecords :: Lens' DescribeConnections (Maybe Int)
describeConnections_maxRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnections' {Maybe Int
maxRecords :: Maybe Int
$sel:maxRecords:DescribeConnections' :: DescribeConnections -> Maybe Int
maxRecords} -> Maybe Int
maxRecords) (\s :: DescribeConnections
s@DescribeConnections' {} Maybe Int
a -> DescribeConnections
s {$sel:maxRecords:DescribeConnections' :: Maybe Int
maxRecords = Maybe Int
a} :: DescribeConnections)

instance Core.AWSPager DescribeConnections where
  page :: DescribeConnections
-> AWSResponse DescribeConnections -> Maybe DescribeConnections
page DescribeConnections
rq AWSResponse DescribeConnections
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeConnections
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeConnectionsResponse (Maybe Text)
describeConnectionsResponse_marker
            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. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeConnections
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeConnectionsResponse (Maybe [Connection])
describeConnectionsResponse_connections
            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.$ DescribeConnections
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeConnections (Maybe Text)
describeConnections_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeConnections
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeConnectionsResponse (Maybe Text)
describeConnectionsResponse_marker
          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 DescribeConnections where
  type
    AWSResponse DescribeConnections =
      DescribeConnectionsResponse
  request :: (Service -> Service)
-> DescribeConnections -> Request DescribeConnections
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 DescribeConnections
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeConnections)))
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 [Connection]
-> Maybe Text -> Int -> DescribeConnectionsResponse
DescribeConnectionsResponse'
            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
"Marker")
            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 DescribeConnections where
  hashWithSalt :: Int -> DescribeConnections -> Int
hashWithSalt Int
_salt DescribeConnections' {Maybe Int
Maybe [Filter]
Maybe Text
maxRecords :: Maybe Int
marker :: Maybe Text
filters :: Maybe [Filter]
$sel:maxRecords:DescribeConnections' :: DescribeConnections -> Maybe Int
$sel:marker:DescribeConnections' :: DescribeConnections -> Maybe Text
$sel:filters:DescribeConnections' :: DescribeConnections -> 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 Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxRecords

instance Prelude.NFData DescribeConnections where
  rnf :: DescribeConnections -> ()
rnf DescribeConnections' {Maybe Int
Maybe [Filter]
Maybe Text
maxRecords :: Maybe Int
marker :: Maybe Text
filters :: Maybe [Filter]
$sel:maxRecords:DescribeConnections' :: DescribeConnections -> Maybe Int
$sel:marker:DescribeConnections' :: DescribeConnections -> Maybe Text
$sel:filters:DescribeConnections' :: DescribeConnections -> 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 Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxRecords

instance Data.ToHeaders DescribeConnections where
  toHeaders :: DescribeConnections -> 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
"AmazonDMSv20160101.DescribeConnections" ::
                          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 DescribeConnections where
  toJSON :: DescribeConnections -> Value
toJSON DescribeConnections' {Maybe Int
Maybe [Filter]
Maybe Text
maxRecords :: Maybe Int
marker :: Maybe Text
filters :: Maybe [Filter]
$sel:maxRecords:DescribeConnections' :: DescribeConnections -> Maybe Int
$sel:marker:DescribeConnections' :: DescribeConnections -> Maybe Text
$sel:filters:DescribeConnections' :: DescribeConnections -> 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
"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,
            (Key
"MaxRecords" 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
maxRecords
          ]
      )

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

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

-- |
--
-- /See:/ 'newDescribeConnectionsResponse' smart constructor.
data DescribeConnectionsResponse = DescribeConnectionsResponse'
  { -- | A description of the connections.
    DescribeConnectionsResponse -> Maybe [Connection]
connections :: Prelude.Maybe [Connection],
    -- | An optional pagination token provided by a previous request. If this
    -- parameter is specified, the response includes only records beyond the
    -- marker, up to the value specified by @MaxRecords@.
    DescribeConnectionsResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeConnectionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeConnectionsResponse -> DescribeConnectionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConnectionsResponse -> DescribeConnectionsResponse -> Bool
$c/= :: DescribeConnectionsResponse -> DescribeConnectionsResponse -> Bool
== :: DescribeConnectionsResponse -> DescribeConnectionsResponse -> Bool
$c== :: DescribeConnectionsResponse -> DescribeConnectionsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeConnectionsResponse]
ReadPrec DescribeConnectionsResponse
Int -> ReadS DescribeConnectionsResponse
ReadS [DescribeConnectionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConnectionsResponse]
$creadListPrec :: ReadPrec [DescribeConnectionsResponse]
readPrec :: ReadPrec DescribeConnectionsResponse
$creadPrec :: ReadPrec DescribeConnectionsResponse
readList :: ReadS [DescribeConnectionsResponse]
$creadList :: ReadS [DescribeConnectionsResponse]
readsPrec :: Int -> ReadS DescribeConnectionsResponse
$creadsPrec :: Int -> ReadS DescribeConnectionsResponse
Prelude.Read, Int -> DescribeConnectionsResponse -> ShowS
[DescribeConnectionsResponse] -> ShowS
DescribeConnectionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConnectionsResponse] -> ShowS
$cshowList :: [DescribeConnectionsResponse] -> ShowS
show :: DescribeConnectionsResponse -> String
$cshow :: DescribeConnectionsResponse -> String
showsPrec :: Int -> DescribeConnectionsResponse -> ShowS
$cshowsPrec :: Int -> DescribeConnectionsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeConnectionsResponse x -> DescribeConnectionsResponse
forall x.
DescribeConnectionsResponse -> Rep DescribeConnectionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeConnectionsResponse x -> DescribeConnectionsResponse
$cfrom :: forall x.
DescribeConnectionsResponse -> Rep DescribeConnectionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConnectionsResponse' 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', 'describeConnectionsResponse_connections' - A description of the connections.
--
-- 'marker', 'describeConnectionsResponse_marker' - An optional pagination token provided by a previous request. If this
-- parameter is specified, the response includes only records beyond the
-- marker, up to the value specified by @MaxRecords@.
--
-- 'httpStatus', 'describeConnectionsResponse_httpStatus' - The response's http status code.
newDescribeConnectionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeConnectionsResponse
newDescribeConnectionsResponse :: Int -> DescribeConnectionsResponse
newDescribeConnectionsResponse Int
pHttpStatus_ =
  DescribeConnectionsResponse'
    { $sel:connections:DescribeConnectionsResponse' :: Maybe [Connection]
connections =
        forall a. Maybe a
Prelude.Nothing,
      $sel:marker:DescribeConnectionsResponse' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeConnectionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A description of the connections.
describeConnectionsResponse_connections :: Lens.Lens' DescribeConnectionsResponse (Prelude.Maybe [Connection])
describeConnectionsResponse_connections :: Lens' DescribeConnectionsResponse (Maybe [Connection])
describeConnectionsResponse_connections = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionsResponse' {Maybe [Connection]
connections :: Maybe [Connection]
$sel:connections:DescribeConnectionsResponse' :: DescribeConnectionsResponse -> Maybe [Connection]
connections} -> Maybe [Connection]
connections) (\s :: DescribeConnectionsResponse
s@DescribeConnectionsResponse' {} Maybe [Connection]
a -> DescribeConnectionsResponse
s {$sel:connections:DescribeConnectionsResponse' :: Maybe [Connection]
connections = Maybe [Connection]
a} :: DescribeConnectionsResponse) 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 pagination token provided by a previous request. If this
-- parameter is specified, the response includes only records beyond the
-- marker, up to the value specified by @MaxRecords@.
describeConnectionsResponse_marker :: Lens.Lens' DescribeConnectionsResponse (Prelude.Maybe Prelude.Text)
describeConnectionsResponse_marker :: Lens' DescribeConnectionsResponse (Maybe Text)
describeConnectionsResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionsResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeConnectionsResponse' :: DescribeConnectionsResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeConnectionsResponse
s@DescribeConnectionsResponse' {} Maybe Text
a -> DescribeConnectionsResponse
s {$sel:marker:DescribeConnectionsResponse' :: Maybe Text
marker = Maybe Text
a} :: DescribeConnectionsResponse)

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

instance Prelude.NFData DescribeConnectionsResponse where
  rnf :: DescribeConnectionsResponse -> ()
rnf DescribeConnectionsResponse' {Int
Maybe [Connection]
Maybe Text
httpStatus :: Int
marker :: Maybe Text
connections :: Maybe [Connection]
$sel:httpStatus:DescribeConnectionsResponse' :: DescribeConnectionsResponse -> Int
$sel:marker:DescribeConnectionsResponse' :: DescribeConnectionsResponse -> Maybe Text
$sel:connections:DescribeConnectionsResponse' :: DescribeConnectionsResponse -> Maybe [Connection]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Connection]
connections
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus