{-# 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.ListConnections
-- 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 connections from the account.
module Amazonka.CloudWatchEvents.ListConnections
  ( -- * Creating a Request
    ListConnections (..),
    newListConnections,

    -- * Request Lenses
    listConnections_connectionState,
    listConnections_limit,
    listConnections_namePrefix,
    listConnections_nextToken,

    -- * Destructuring the Response
    ListConnectionsResponse (..),
    newListConnectionsResponse,

    -- * Response Lenses
    listConnectionsResponse_connections,
    listConnectionsResponse_nextToken,
    listConnectionsResponse_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:/ 'newListConnections' smart constructor.
data ListConnections = ListConnections'
  { -- | The state of the connection.
    ListConnections -> Maybe ConnectionState
connectionState :: Prelude.Maybe ConnectionState,
    -- | The maximum number of connections to return.
    ListConnections -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | A name prefix to filter results returned. Only connections with a name
    -- that starts with the prefix are returned.
    ListConnections -> Maybe Text
namePrefix :: Prelude.Maybe Prelude.Text,
    -- | The token returned by a previous call to retrieve the next set of
    -- results.
    ListConnections -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListConnections -> ListConnections -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListConnections -> ListConnections -> Bool
$c/= :: ListConnections -> ListConnections -> Bool
== :: ListConnections -> ListConnections -> Bool
$c== :: ListConnections -> ListConnections -> Bool
Prelude.Eq, ReadPrec [ListConnections]
ReadPrec ListConnections
Int -> ReadS ListConnections
ReadS [ListConnections]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListConnections]
$creadListPrec :: ReadPrec [ListConnections]
readPrec :: ReadPrec ListConnections
$creadPrec :: ReadPrec ListConnections
readList :: ReadS [ListConnections]
$creadList :: ReadS [ListConnections]
readsPrec :: Int -> ReadS ListConnections
$creadsPrec :: Int -> ReadS ListConnections
Prelude.Read, Int -> ListConnections -> ShowS
[ListConnections] -> ShowS
ListConnections -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListConnections] -> ShowS
$cshowList :: [ListConnections] -> ShowS
show :: ListConnections -> String
$cshow :: ListConnections -> String
showsPrec :: Int -> ListConnections -> ShowS
$cshowsPrec :: Int -> ListConnections -> ShowS
Prelude.Show, forall x. Rep ListConnections x -> ListConnections
forall x. ListConnections -> Rep ListConnections x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListConnections x -> ListConnections
$cfrom :: forall x. ListConnections -> Rep ListConnections x
Prelude.Generic)

-- |
-- Create a value of 'ListConnections' 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:
--
-- 'connectionState', 'listConnections_connectionState' - The state of the connection.
--
-- 'limit', 'listConnections_limit' - The maximum number of connections to return.
--
-- 'namePrefix', 'listConnections_namePrefix' - A name prefix to filter results returned. Only connections with a name
-- that starts with the prefix are returned.
--
-- 'nextToken', 'listConnections_nextToken' - The token returned by a previous call to retrieve the next set of
-- results.
newListConnections ::
  ListConnections
newListConnections :: ListConnections
newListConnections =
  ListConnections'
    { $sel:connectionState:ListConnections' :: Maybe ConnectionState
connectionState = forall a. Maybe a
Prelude.Nothing,
      $sel:limit:ListConnections' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:namePrefix:ListConnections' :: Maybe Text
namePrefix = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListConnections' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The state of the connection.
listConnections_connectionState :: Lens.Lens' ListConnections (Prelude.Maybe ConnectionState)
listConnections_connectionState :: Lens' ListConnections (Maybe ConnectionState)
listConnections_connectionState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConnections' {Maybe ConnectionState
connectionState :: Maybe ConnectionState
$sel:connectionState:ListConnections' :: ListConnections -> Maybe ConnectionState
connectionState} -> Maybe ConnectionState
connectionState) (\s :: ListConnections
s@ListConnections' {} Maybe ConnectionState
a -> ListConnections
s {$sel:connectionState:ListConnections' :: Maybe ConnectionState
connectionState = Maybe ConnectionState
a} :: ListConnections)

-- | The maximum number of connections to return.
listConnections_limit :: Lens.Lens' ListConnections (Prelude.Maybe Prelude.Natural)
listConnections_limit :: Lens' ListConnections (Maybe Natural)
listConnections_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConnections' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListConnections' :: ListConnections -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListConnections
s@ListConnections' {} Maybe Natural
a -> ListConnections
s {$sel:limit:ListConnections' :: Maybe Natural
limit = Maybe Natural
a} :: ListConnections)

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

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

instance Core.AWSRequest ListConnections where
  type
    AWSResponse ListConnections =
      ListConnectionsResponse
  request :: (Service -> Service) -> ListConnections -> Request ListConnections
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 ListConnections
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListConnections)))
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 -> ListConnectionsResponse
ListConnectionsResponse'
            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 ListConnections where
  hashWithSalt :: Int -> ListConnections -> Int
hashWithSalt Int
_salt ListConnections' {Maybe Natural
Maybe Text
Maybe ConnectionState
nextToken :: Maybe Text
namePrefix :: Maybe Text
limit :: Maybe Natural
connectionState :: Maybe ConnectionState
$sel:nextToken:ListConnections' :: ListConnections -> Maybe Text
$sel:namePrefix:ListConnections' :: ListConnections -> Maybe Text
$sel:limit:ListConnections' :: ListConnections -> Maybe Natural
$sel:connectionState:ListConnections' :: ListConnections -> Maybe ConnectionState
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectionState
connectionState
      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 ListConnections where
  rnf :: ListConnections -> ()
rnf ListConnections' {Maybe Natural
Maybe Text
Maybe ConnectionState
nextToken :: Maybe Text
namePrefix :: Maybe Text
limit :: Maybe Natural
connectionState :: Maybe ConnectionState
$sel:nextToken:ListConnections' :: ListConnections -> Maybe Text
$sel:namePrefix:ListConnections' :: ListConnections -> Maybe Text
$sel:limit:ListConnections' :: ListConnections -> Maybe Natural
$sel:connectionState:ListConnections' :: ListConnections -> Maybe ConnectionState
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectionState
connectionState
      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 ListConnections where
  toHeaders :: ListConnections -> 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.ListConnections" :: 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 ListConnections where
  toJSON :: ListConnections -> Value
toJSON ListConnections' {Maybe Natural
Maybe Text
Maybe ConnectionState
nextToken :: Maybe Text
namePrefix :: Maybe Text
limit :: Maybe Natural
connectionState :: Maybe ConnectionState
$sel:nextToken:ListConnections' :: ListConnections -> Maybe Text
$sel:namePrefix:ListConnections' :: ListConnections -> Maybe Text
$sel:limit:ListConnections' :: ListConnections -> Maybe Natural
$sel:connectionState:ListConnections' :: ListConnections -> Maybe ConnectionState
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ConnectionState" 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 ConnectionState
connectionState,
            (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 ListConnections where
  toPath :: ListConnections -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'ListConnectionsResponse' 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', 'listConnectionsResponse_connections' - An array of connections objects that include details about the
-- connections.
--
-- 'nextToken', 'listConnectionsResponse_nextToken' - A token you can use in a subsequent request to retrieve the next set of
-- results.
--
-- 'httpStatus', 'listConnectionsResponse_httpStatus' - The response's http status code.
newListConnectionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListConnectionsResponse
newListConnectionsResponse :: Int -> ListConnectionsResponse
newListConnectionsResponse Int
pHttpStatus_ =
  ListConnectionsResponse'
    { $sel:connections:ListConnectionsResponse' :: Maybe [Connection]
connections =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListConnectionsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListConnectionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of connections objects that include details about the
-- connections.
listConnectionsResponse_connections :: Lens.Lens' ListConnectionsResponse (Prelude.Maybe [Connection])
listConnectionsResponse_connections :: Lens' ListConnectionsResponse (Maybe [Connection])
listConnectionsResponse_connections = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConnectionsResponse' {Maybe [Connection]
connections :: Maybe [Connection]
$sel:connections:ListConnectionsResponse' :: ListConnectionsResponse -> Maybe [Connection]
connections} -> Maybe [Connection]
connections) (\s :: ListConnectionsResponse
s@ListConnectionsResponse' {} Maybe [Connection]
a -> ListConnectionsResponse
s {$sel:connections:ListConnectionsResponse' :: Maybe [Connection]
connections = Maybe [Connection]
a} :: ListConnectionsResponse) 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.
listConnectionsResponse_nextToken :: Lens.Lens' ListConnectionsResponse (Prelude.Maybe Prelude.Text)
listConnectionsResponse_nextToken :: Lens' ListConnectionsResponse (Maybe Text)
listConnectionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConnectionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListConnectionsResponse' :: ListConnectionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListConnectionsResponse
s@ListConnectionsResponse' {} Maybe Text
a -> ListConnectionsResponse
s {$sel:nextToken:ListConnectionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListConnectionsResponse)

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

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