{-# 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.Glue.GetConnections
-- 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 connection definitions from the Data Catalog.
--
-- This operation returns paginated results.
module Amazonka.Glue.GetConnections
  ( -- * Creating a Request
    GetConnections (..),
    newGetConnections,

    -- * Request Lenses
    getConnections_catalogId,
    getConnections_filter,
    getConnections_hidePassword,
    getConnections_maxResults,
    getConnections_nextToken,

    -- * Destructuring the Response
    GetConnectionsResponse (..),
    newGetConnectionsResponse,

    -- * Response Lenses
    getConnectionsResponse_connectionList,
    getConnectionsResponse_nextToken,
    getConnectionsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetConnections' smart constructor.
data GetConnections = GetConnections'
  { -- | The ID of the Data Catalog in which the connections reside. If none is
    -- provided, the Amazon Web Services account ID is used by default.
    GetConnections -> Maybe Text
catalogId :: Prelude.Maybe Prelude.Text,
    -- | A filter that controls which connections are returned.
    GetConnections -> Maybe GetConnectionsFilter
filter' :: Prelude.Maybe GetConnectionsFilter,
    -- | Allows you to retrieve the connection metadata without returning the
    -- password. For instance, the Glue console uses this flag to retrieve the
    -- connection, and does not display the password. Set this parameter when
    -- the caller might not have permission to use the KMS key to decrypt the
    -- password, but it does have permission to access the rest of the
    -- connection properties.
    GetConnections -> Maybe Bool
hidePassword :: Prelude.Maybe Prelude.Bool,
    -- | The maximum number of connections to return in one response.
    GetConnections -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A continuation token, if this is a continuation call.
    GetConnections -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (GetConnections -> GetConnections -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetConnections -> GetConnections -> Bool
$c/= :: GetConnections -> GetConnections -> Bool
== :: GetConnections -> GetConnections -> Bool
$c== :: GetConnections -> GetConnections -> Bool
Prelude.Eq, ReadPrec [GetConnections]
ReadPrec GetConnections
Int -> ReadS GetConnections
ReadS [GetConnections]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetConnections]
$creadListPrec :: ReadPrec [GetConnections]
readPrec :: ReadPrec GetConnections
$creadPrec :: ReadPrec GetConnections
readList :: ReadS [GetConnections]
$creadList :: ReadS [GetConnections]
readsPrec :: Int -> ReadS GetConnections
$creadsPrec :: Int -> ReadS GetConnections
Prelude.Read, Int -> GetConnections -> ShowS
[GetConnections] -> ShowS
GetConnections -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetConnections] -> ShowS
$cshowList :: [GetConnections] -> ShowS
show :: GetConnections -> String
$cshow :: GetConnections -> String
showsPrec :: Int -> GetConnections -> ShowS
$cshowsPrec :: Int -> GetConnections -> ShowS
Prelude.Show, forall x. Rep GetConnections x -> GetConnections
forall x. GetConnections -> Rep GetConnections x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetConnections x -> GetConnections
$cfrom :: forall x. GetConnections -> Rep GetConnections x
Prelude.Generic)

-- |
-- Create a value of 'GetConnections' 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:
--
-- 'catalogId', 'getConnections_catalogId' - The ID of the Data Catalog in which the connections reside. If none is
-- provided, the Amazon Web Services account ID is used by default.
--
-- 'filter'', 'getConnections_filter' - A filter that controls which connections are returned.
--
-- 'hidePassword', 'getConnections_hidePassword' - Allows you to retrieve the connection metadata without returning the
-- password. For instance, the Glue console uses this flag to retrieve the
-- connection, and does not display the password. Set this parameter when
-- the caller might not have permission to use the KMS key to decrypt the
-- password, but it does have permission to access the rest of the
-- connection properties.
--
-- 'maxResults', 'getConnections_maxResults' - The maximum number of connections to return in one response.
--
-- 'nextToken', 'getConnections_nextToken' - A continuation token, if this is a continuation call.
newGetConnections ::
  GetConnections
newGetConnections :: GetConnections
newGetConnections =
  GetConnections'
    { $sel:catalogId:GetConnections' :: Maybe Text
catalogId = forall a. Maybe a
Prelude.Nothing,
      $sel:filter':GetConnections' :: Maybe GetConnectionsFilter
filter' = forall a. Maybe a
Prelude.Nothing,
      $sel:hidePassword:GetConnections' :: Maybe Bool
hidePassword = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:GetConnections' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetConnections' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The ID of the Data Catalog in which the connections reside. If none is
-- provided, the Amazon Web Services account ID is used by default.
getConnections_catalogId :: Lens.Lens' GetConnections (Prelude.Maybe Prelude.Text)
getConnections_catalogId :: Lens' GetConnections (Maybe Text)
getConnections_catalogId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConnections' {Maybe Text
catalogId :: Maybe Text
$sel:catalogId:GetConnections' :: GetConnections -> Maybe Text
catalogId} -> Maybe Text
catalogId) (\s :: GetConnections
s@GetConnections' {} Maybe Text
a -> GetConnections
s {$sel:catalogId:GetConnections' :: Maybe Text
catalogId = Maybe Text
a} :: GetConnections)

-- | A filter that controls which connections are returned.
getConnections_filter :: Lens.Lens' GetConnections (Prelude.Maybe GetConnectionsFilter)
getConnections_filter :: Lens' GetConnections (Maybe GetConnectionsFilter)
getConnections_filter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConnections' {Maybe GetConnectionsFilter
filter' :: Maybe GetConnectionsFilter
$sel:filter':GetConnections' :: GetConnections -> Maybe GetConnectionsFilter
filter'} -> Maybe GetConnectionsFilter
filter') (\s :: GetConnections
s@GetConnections' {} Maybe GetConnectionsFilter
a -> GetConnections
s {$sel:filter':GetConnections' :: Maybe GetConnectionsFilter
filter' = Maybe GetConnectionsFilter
a} :: GetConnections)

-- | Allows you to retrieve the connection metadata without returning the
-- password. For instance, the Glue console uses this flag to retrieve the
-- connection, and does not display the password. Set this parameter when
-- the caller might not have permission to use the KMS key to decrypt the
-- password, but it does have permission to access the rest of the
-- connection properties.
getConnections_hidePassword :: Lens.Lens' GetConnections (Prelude.Maybe Prelude.Bool)
getConnections_hidePassword :: Lens' GetConnections (Maybe Bool)
getConnections_hidePassword = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConnections' {Maybe Bool
hidePassword :: Maybe Bool
$sel:hidePassword:GetConnections' :: GetConnections -> Maybe Bool
hidePassword} -> Maybe Bool
hidePassword) (\s :: GetConnections
s@GetConnections' {} Maybe Bool
a -> GetConnections
s {$sel:hidePassword:GetConnections' :: Maybe Bool
hidePassword = Maybe Bool
a} :: GetConnections)

-- | The maximum number of connections to return in one response.
getConnections_maxResults :: Lens.Lens' GetConnections (Prelude.Maybe Prelude.Natural)
getConnections_maxResults :: Lens' GetConnections (Maybe Natural)
getConnections_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConnections' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetConnections' :: GetConnections -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetConnections
s@GetConnections' {} Maybe Natural
a -> GetConnections
s {$sel:maxResults:GetConnections' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetConnections)

-- | A continuation token, if this is a continuation call.
getConnections_nextToken :: Lens.Lens' GetConnections (Prelude.Maybe Prelude.Text)
getConnections_nextToken :: Lens' GetConnections (Maybe Text)
getConnections_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConnections' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetConnections' :: GetConnections -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetConnections
s@GetConnections' {} Maybe Text
a -> GetConnections
s {$sel:nextToken:GetConnections' :: Maybe Text
nextToken = Maybe Text
a} :: GetConnections)

instance Core.AWSPager GetConnections where
  page :: GetConnections
-> AWSResponse GetConnections -> Maybe GetConnections
page GetConnections
rq AWSResponse GetConnections
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetConnections
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetConnectionsResponse (Maybe Text)
getConnectionsResponse_nextToken
            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 GetConnections
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetConnectionsResponse (Maybe [Connection])
getConnectionsResponse_connectionList
            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.$ GetConnections
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetConnections (Maybe Text)
getConnections_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetConnections
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetConnectionsResponse (Maybe Text)
getConnectionsResponse_nextToken
          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 GetConnections where
  type
    AWSResponse GetConnections =
      GetConnectionsResponse
  request :: (Service -> Service) -> GetConnections -> Request GetConnections
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 GetConnections
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetConnections)))
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 -> GetConnectionsResponse
GetConnectionsResponse'
            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
"ConnectionList" 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 GetConnections where
  hashWithSalt :: Int -> GetConnections -> Int
hashWithSalt Int
_salt GetConnections' {Maybe Bool
Maybe Natural
Maybe Text
Maybe GetConnectionsFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
hidePassword :: Maybe Bool
filter' :: Maybe GetConnectionsFilter
catalogId :: Maybe Text
$sel:nextToken:GetConnections' :: GetConnections -> Maybe Text
$sel:maxResults:GetConnections' :: GetConnections -> Maybe Natural
$sel:hidePassword:GetConnections' :: GetConnections -> Maybe Bool
$sel:filter':GetConnections' :: GetConnections -> Maybe GetConnectionsFilter
$sel:catalogId:GetConnections' :: GetConnections -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
catalogId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe GetConnectionsFilter
filter'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
hidePassword
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData GetConnections where
  rnf :: GetConnections -> ()
rnf GetConnections' {Maybe Bool
Maybe Natural
Maybe Text
Maybe GetConnectionsFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
hidePassword :: Maybe Bool
filter' :: Maybe GetConnectionsFilter
catalogId :: Maybe Text
$sel:nextToken:GetConnections' :: GetConnections -> Maybe Text
$sel:maxResults:GetConnections' :: GetConnections -> Maybe Natural
$sel:hidePassword:GetConnections' :: GetConnections -> Maybe Bool
$sel:filter':GetConnections' :: GetConnections -> Maybe GetConnectionsFilter
$sel:catalogId:GetConnections' :: GetConnections -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
catalogId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe GetConnectionsFilter
filter'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
hidePassword
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders GetConnections where
  toHeaders :: GetConnections -> 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
"AWSGlue.GetConnections" :: 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 GetConnections where
  toJSON :: GetConnections -> Value
toJSON GetConnections' {Maybe Bool
Maybe Natural
Maybe Text
Maybe GetConnectionsFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
hidePassword :: Maybe Bool
filter' :: Maybe GetConnectionsFilter
catalogId :: Maybe Text
$sel:nextToken:GetConnections' :: GetConnections -> Maybe Text
$sel:maxResults:GetConnections' :: GetConnections -> Maybe Natural
$sel:hidePassword:GetConnections' :: GetConnections -> Maybe Bool
$sel:filter':GetConnections' :: GetConnections -> Maybe GetConnectionsFilter
$sel:catalogId:GetConnections' :: GetConnections -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CatalogId" 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
catalogId,
            (Key
"Filter" 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 GetConnectionsFilter
filter',
            (Key
"HidePassword" 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 Bool
hidePassword,
            (Key
"MaxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken
          ]
      )

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

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

-- | /See:/ 'newGetConnectionsResponse' smart constructor.
data GetConnectionsResponse = GetConnectionsResponse'
  { -- | A list of requested connection definitions.
    GetConnectionsResponse -> Maybe [Connection]
connectionList :: Prelude.Maybe [Connection],
    -- | A continuation token, if the list of connections returned does not
    -- include the last of the filtered connections.
    GetConnectionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetConnectionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetConnectionsResponse -> GetConnectionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetConnectionsResponse -> GetConnectionsResponse -> Bool
$c/= :: GetConnectionsResponse -> GetConnectionsResponse -> Bool
== :: GetConnectionsResponse -> GetConnectionsResponse -> Bool
$c== :: GetConnectionsResponse -> GetConnectionsResponse -> Bool
Prelude.Eq, ReadPrec [GetConnectionsResponse]
ReadPrec GetConnectionsResponse
Int -> ReadS GetConnectionsResponse
ReadS [GetConnectionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetConnectionsResponse]
$creadListPrec :: ReadPrec [GetConnectionsResponse]
readPrec :: ReadPrec GetConnectionsResponse
$creadPrec :: ReadPrec GetConnectionsResponse
readList :: ReadS [GetConnectionsResponse]
$creadList :: ReadS [GetConnectionsResponse]
readsPrec :: Int -> ReadS GetConnectionsResponse
$creadsPrec :: Int -> ReadS GetConnectionsResponse
Prelude.Read, Int -> GetConnectionsResponse -> ShowS
[GetConnectionsResponse] -> ShowS
GetConnectionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetConnectionsResponse] -> ShowS
$cshowList :: [GetConnectionsResponse] -> ShowS
show :: GetConnectionsResponse -> String
$cshow :: GetConnectionsResponse -> String
showsPrec :: Int -> GetConnectionsResponse -> ShowS
$cshowsPrec :: Int -> GetConnectionsResponse -> ShowS
Prelude.Show, forall x. Rep GetConnectionsResponse x -> GetConnectionsResponse
forall x. GetConnectionsResponse -> Rep GetConnectionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetConnectionsResponse x -> GetConnectionsResponse
$cfrom :: forall x. GetConnectionsResponse -> Rep GetConnectionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetConnectionsResponse' 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:
--
-- 'connectionList', 'getConnectionsResponse_connectionList' - A list of requested connection definitions.
--
-- 'nextToken', 'getConnectionsResponse_nextToken' - A continuation token, if the list of connections returned does not
-- include the last of the filtered connections.
--
-- 'httpStatus', 'getConnectionsResponse_httpStatus' - The response's http status code.
newGetConnectionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetConnectionsResponse
newGetConnectionsResponse :: Int -> GetConnectionsResponse
newGetConnectionsResponse Int
pHttpStatus_ =
  GetConnectionsResponse'
    { $sel:connectionList:GetConnectionsResponse' :: Maybe [Connection]
connectionList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetConnectionsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetConnectionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of requested connection definitions.
getConnectionsResponse_connectionList :: Lens.Lens' GetConnectionsResponse (Prelude.Maybe [Connection])
getConnectionsResponse_connectionList :: Lens' GetConnectionsResponse (Maybe [Connection])
getConnectionsResponse_connectionList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConnectionsResponse' {Maybe [Connection]
connectionList :: Maybe [Connection]
$sel:connectionList:GetConnectionsResponse' :: GetConnectionsResponse -> Maybe [Connection]
connectionList} -> Maybe [Connection]
connectionList) (\s :: GetConnectionsResponse
s@GetConnectionsResponse' {} Maybe [Connection]
a -> GetConnectionsResponse
s {$sel:connectionList:GetConnectionsResponse' :: Maybe [Connection]
connectionList = Maybe [Connection]
a} :: GetConnectionsResponse) 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 continuation token, if the list of connections returned does not
-- include the last of the filtered connections.
getConnectionsResponse_nextToken :: Lens.Lens' GetConnectionsResponse (Prelude.Maybe Prelude.Text)
getConnectionsResponse_nextToken :: Lens' GetConnectionsResponse (Maybe Text)
getConnectionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConnectionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetConnectionsResponse' :: GetConnectionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetConnectionsResponse
s@GetConnectionsResponse' {} Maybe Text
a -> GetConnectionsResponse
s {$sel:nextToken:GetConnectionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetConnectionsResponse)

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

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