{-# 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.DescribeConnection
-- 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 details about a connection.
module Amazonka.CloudWatchEvents.DescribeConnection
  ( -- * Creating a Request
    DescribeConnection (..),
    newDescribeConnection,

    -- * Request Lenses
    describeConnection_name,

    -- * Destructuring the Response
    DescribeConnectionResponse (..),
    newDescribeConnectionResponse,

    -- * Response Lenses
    describeConnectionResponse_authParameters,
    describeConnectionResponse_authorizationType,
    describeConnectionResponse_connectionArn,
    describeConnectionResponse_connectionState,
    describeConnectionResponse_creationTime,
    describeConnectionResponse_description,
    describeConnectionResponse_lastAuthorizedTime,
    describeConnectionResponse_lastModifiedTime,
    describeConnectionResponse_name,
    describeConnectionResponse_secretArn,
    describeConnectionResponse_stateReason,
    describeConnectionResponse_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:/ 'newDescribeConnection' smart constructor.
data DescribeConnection = DescribeConnection'
  { -- | The name of the connection to retrieve.
    DescribeConnection -> Text
name :: Prelude.Text
  }
  deriving (DescribeConnection -> DescribeConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConnection -> DescribeConnection -> Bool
$c/= :: DescribeConnection -> DescribeConnection -> Bool
== :: DescribeConnection -> DescribeConnection -> Bool
$c== :: DescribeConnection -> DescribeConnection -> Bool
Prelude.Eq, ReadPrec [DescribeConnection]
ReadPrec DescribeConnection
Int -> ReadS DescribeConnection
ReadS [DescribeConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConnection]
$creadListPrec :: ReadPrec [DescribeConnection]
readPrec :: ReadPrec DescribeConnection
$creadPrec :: ReadPrec DescribeConnection
readList :: ReadS [DescribeConnection]
$creadList :: ReadS [DescribeConnection]
readsPrec :: Int -> ReadS DescribeConnection
$creadsPrec :: Int -> ReadS DescribeConnection
Prelude.Read, Int -> DescribeConnection -> ShowS
[DescribeConnection] -> ShowS
DescribeConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConnection] -> ShowS
$cshowList :: [DescribeConnection] -> ShowS
show :: DescribeConnection -> String
$cshow :: DescribeConnection -> String
showsPrec :: Int -> DescribeConnection -> ShowS
$cshowsPrec :: Int -> DescribeConnection -> ShowS
Prelude.Show, forall x. Rep DescribeConnection x -> DescribeConnection
forall x. DescribeConnection -> Rep DescribeConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeConnection x -> DescribeConnection
$cfrom :: forall x. DescribeConnection -> Rep DescribeConnection x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConnection' 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:
--
-- 'name', 'describeConnection_name' - The name of the connection to retrieve.
newDescribeConnection ::
  -- | 'name'
  Prelude.Text ->
  DescribeConnection
newDescribeConnection :: Text -> DescribeConnection
newDescribeConnection Text
pName_ =
  DescribeConnection' {$sel:name:DescribeConnection' :: Text
name = Text
pName_}

-- | The name of the connection to retrieve.
describeConnection_name :: Lens.Lens' DescribeConnection Prelude.Text
describeConnection_name :: Lens' DescribeConnection Text
describeConnection_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnection' {Text
name :: Text
$sel:name:DescribeConnection' :: DescribeConnection -> Text
name} -> Text
name) (\s :: DescribeConnection
s@DescribeConnection' {} Text
a -> DescribeConnection
s {$sel:name:DescribeConnection' :: Text
name = Text
a} :: DescribeConnection)

instance Core.AWSRequest DescribeConnection where
  type
    AWSResponse DescribeConnection =
      DescribeConnectionResponse
  request :: (Service -> Service)
-> DescribeConnection -> Request DescribeConnection
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 DescribeConnection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeConnection)))
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 ConnectionAuthResponseParameters
-> Maybe ConnectionAuthorizationType
-> Maybe Text
-> Maybe ConnectionState
-> Maybe POSIX
-> Maybe Text
-> Maybe POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> DescribeConnectionResponse
DescribeConnectionResponse'
            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
"AuthParameters")
            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
"AuthorizationType")
            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
"ConnectionArn")
            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
"ConnectionState")
            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
"CreationTime")
            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
"Description")
            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
"LastAuthorizedTime")
            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
"LastModifiedTime")
            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
"Name")
            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
"SecretArn")
            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
"StateReason")
            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 DescribeConnection where
  hashWithSalt :: Int -> DescribeConnection -> Int
hashWithSalt Int
_salt DescribeConnection' {Text
name :: Text
$sel:name:DescribeConnection' :: DescribeConnection -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData DescribeConnection where
  rnf :: DescribeConnection -> ()
rnf DescribeConnection' {Text
name :: Text
$sel:name:DescribeConnection' :: DescribeConnection -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders DescribeConnection where
  toHeaders :: DescribeConnection -> 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.DescribeConnection" ::
                          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 DescribeConnection where
  toJSON :: DescribeConnection -> Value
toJSON DescribeConnection' {Text
name :: Text
$sel:name:DescribeConnection' :: DescribeConnection -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)]
      )

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

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

-- | /See:/ 'newDescribeConnectionResponse' smart constructor.
data DescribeConnectionResponse = DescribeConnectionResponse'
  { -- | The parameters to use for authorization for the connection.
    DescribeConnectionResponse
-> Maybe ConnectionAuthResponseParameters
authParameters :: Prelude.Maybe ConnectionAuthResponseParameters,
    -- | The type of authorization specified for the connection.
    DescribeConnectionResponse -> Maybe ConnectionAuthorizationType
authorizationType :: Prelude.Maybe ConnectionAuthorizationType,
    -- | The ARN of the connection retrieved.
    DescribeConnectionResponse -> Maybe Text
connectionArn :: Prelude.Maybe Prelude.Text,
    -- | The state of the connection retrieved.
    DescribeConnectionResponse -> Maybe ConnectionState
connectionState :: Prelude.Maybe ConnectionState,
    -- | A time stamp for the time that the connection was created.
    DescribeConnectionResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The description for the connection retrieved.
    DescribeConnectionResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A time stamp for the time that the connection was last authorized.
    DescribeConnectionResponse -> Maybe POSIX
lastAuthorizedTime :: Prelude.Maybe Data.POSIX,
    -- | A time stamp for the time that the connection was last modified.
    DescribeConnectionResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the connection retrieved.
    DescribeConnectionResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the secret created from the authorization parameters
    -- specified for the connection.
    DescribeConnectionResponse -> Maybe Text
secretArn :: Prelude.Maybe Prelude.Text,
    -- | The reason that the connection is in the current connection state.
    DescribeConnectionResponse -> Maybe Text
stateReason :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeConnectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeConnectionResponse -> DescribeConnectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConnectionResponse -> DescribeConnectionResponse -> Bool
$c/= :: DescribeConnectionResponse -> DescribeConnectionResponse -> Bool
== :: DescribeConnectionResponse -> DescribeConnectionResponse -> Bool
$c== :: DescribeConnectionResponse -> DescribeConnectionResponse -> Bool
Prelude.Eq, ReadPrec [DescribeConnectionResponse]
ReadPrec DescribeConnectionResponse
Int -> ReadS DescribeConnectionResponse
ReadS [DescribeConnectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConnectionResponse]
$creadListPrec :: ReadPrec [DescribeConnectionResponse]
readPrec :: ReadPrec DescribeConnectionResponse
$creadPrec :: ReadPrec DescribeConnectionResponse
readList :: ReadS [DescribeConnectionResponse]
$creadList :: ReadS [DescribeConnectionResponse]
readsPrec :: Int -> ReadS DescribeConnectionResponse
$creadsPrec :: Int -> ReadS DescribeConnectionResponse
Prelude.Read, Int -> DescribeConnectionResponse -> ShowS
[DescribeConnectionResponse] -> ShowS
DescribeConnectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConnectionResponse] -> ShowS
$cshowList :: [DescribeConnectionResponse] -> ShowS
show :: DescribeConnectionResponse -> String
$cshow :: DescribeConnectionResponse -> String
showsPrec :: Int -> DescribeConnectionResponse -> ShowS
$cshowsPrec :: Int -> DescribeConnectionResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeConnectionResponse x -> DescribeConnectionResponse
forall x.
DescribeConnectionResponse -> Rep DescribeConnectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeConnectionResponse x -> DescribeConnectionResponse
$cfrom :: forall x.
DescribeConnectionResponse -> Rep DescribeConnectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConnectionResponse' 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:
--
-- 'authParameters', 'describeConnectionResponse_authParameters' - The parameters to use for authorization for the connection.
--
-- 'authorizationType', 'describeConnectionResponse_authorizationType' - The type of authorization specified for the connection.
--
-- 'connectionArn', 'describeConnectionResponse_connectionArn' - The ARN of the connection retrieved.
--
-- 'connectionState', 'describeConnectionResponse_connectionState' - The state of the connection retrieved.
--
-- 'creationTime', 'describeConnectionResponse_creationTime' - A time stamp for the time that the connection was created.
--
-- 'description', 'describeConnectionResponse_description' - The description for the connection retrieved.
--
-- 'lastAuthorizedTime', 'describeConnectionResponse_lastAuthorizedTime' - A time stamp for the time that the connection was last authorized.
--
-- 'lastModifiedTime', 'describeConnectionResponse_lastModifiedTime' - A time stamp for the time that the connection was last modified.
--
-- 'name', 'describeConnectionResponse_name' - The name of the connection retrieved.
--
-- 'secretArn', 'describeConnectionResponse_secretArn' - The ARN of the secret created from the authorization parameters
-- specified for the connection.
--
-- 'stateReason', 'describeConnectionResponse_stateReason' - The reason that the connection is in the current connection state.
--
-- 'httpStatus', 'describeConnectionResponse_httpStatus' - The response's http status code.
newDescribeConnectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeConnectionResponse
newDescribeConnectionResponse :: Int -> DescribeConnectionResponse
newDescribeConnectionResponse Int
pHttpStatus_ =
  DescribeConnectionResponse'
    { $sel:authParameters:DescribeConnectionResponse' :: Maybe ConnectionAuthResponseParameters
authParameters =
        forall a. Maybe a
Prelude.Nothing,
      $sel:authorizationType:DescribeConnectionResponse' :: Maybe ConnectionAuthorizationType
authorizationType = forall a. Maybe a
Prelude.Nothing,
      $sel:connectionArn:DescribeConnectionResponse' :: Maybe Text
connectionArn = forall a. Maybe a
Prelude.Nothing,
      $sel:connectionState:DescribeConnectionResponse' :: Maybe ConnectionState
connectionState = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:DescribeConnectionResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:description:DescribeConnectionResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:lastAuthorizedTime:DescribeConnectionResponse' :: Maybe POSIX
lastAuthorizedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:DescribeConnectionResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:name:DescribeConnectionResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:secretArn:DescribeConnectionResponse' :: Maybe Text
secretArn = forall a. Maybe a
Prelude.Nothing,
      $sel:stateReason:DescribeConnectionResponse' :: Maybe Text
stateReason = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeConnectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The parameters to use for authorization for the connection.
describeConnectionResponse_authParameters :: Lens.Lens' DescribeConnectionResponse (Prelude.Maybe ConnectionAuthResponseParameters)
describeConnectionResponse_authParameters :: Lens'
  DescribeConnectionResponse (Maybe ConnectionAuthResponseParameters)
describeConnectionResponse_authParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionResponse' {Maybe ConnectionAuthResponseParameters
authParameters :: Maybe ConnectionAuthResponseParameters
$sel:authParameters:DescribeConnectionResponse' :: DescribeConnectionResponse
-> Maybe ConnectionAuthResponseParameters
authParameters} -> Maybe ConnectionAuthResponseParameters
authParameters) (\s :: DescribeConnectionResponse
s@DescribeConnectionResponse' {} Maybe ConnectionAuthResponseParameters
a -> DescribeConnectionResponse
s {$sel:authParameters:DescribeConnectionResponse' :: Maybe ConnectionAuthResponseParameters
authParameters = Maybe ConnectionAuthResponseParameters
a} :: DescribeConnectionResponse)

-- | The type of authorization specified for the connection.
describeConnectionResponse_authorizationType :: Lens.Lens' DescribeConnectionResponse (Prelude.Maybe ConnectionAuthorizationType)
describeConnectionResponse_authorizationType :: Lens'
  DescribeConnectionResponse (Maybe ConnectionAuthorizationType)
describeConnectionResponse_authorizationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionResponse' {Maybe ConnectionAuthorizationType
authorizationType :: Maybe ConnectionAuthorizationType
$sel:authorizationType:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe ConnectionAuthorizationType
authorizationType} -> Maybe ConnectionAuthorizationType
authorizationType) (\s :: DescribeConnectionResponse
s@DescribeConnectionResponse' {} Maybe ConnectionAuthorizationType
a -> DescribeConnectionResponse
s {$sel:authorizationType:DescribeConnectionResponse' :: Maybe ConnectionAuthorizationType
authorizationType = Maybe ConnectionAuthorizationType
a} :: DescribeConnectionResponse)

-- | The ARN of the connection retrieved.
describeConnectionResponse_connectionArn :: Lens.Lens' DescribeConnectionResponse (Prelude.Maybe Prelude.Text)
describeConnectionResponse_connectionArn :: Lens' DescribeConnectionResponse (Maybe Text)
describeConnectionResponse_connectionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionResponse' {Maybe Text
connectionArn :: Maybe Text
$sel:connectionArn:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe Text
connectionArn} -> Maybe Text
connectionArn) (\s :: DescribeConnectionResponse
s@DescribeConnectionResponse' {} Maybe Text
a -> DescribeConnectionResponse
s {$sel:connectionArn:DescribeConnectionResponse' :: Maybe Text
connectionArn = Maybe Text
a} :: DescribeConnectionResponse)

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

-- | A time stamp for the time that the connection was created.
describeConnectionResponse_creationTime :: Lens.Lens' DescribeConnectionResponse (Prelude.Maybe Prelude.UTCTime)
describeConnectionResponse_creationTime :: Lens' DescribeConnectionResponse (Maybe UTCTime)
describeConnectionResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeConnectionResponse
s@DescribeConnectionResponse' {} Maybe POSIX
a -> DescribeConnectionResponse
s {$sel:creationTime:DescribeConnectionResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeConnectionResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The description for the connection retrieved.
describeConnectionResponse_description :: Lens.Lens' DescribeConnectionResponse (Prelude.Maybe Prelude.Text)
describeConnectionResponse_description :: Lens' DescribeConnectionResponse (Maybe Text)
describeConnectionResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionResponse' {Maybe Text
description :: Maybe Text
$sel:description:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: DescribeConnectionResponse
s@DescribeConnectionResponse' {} Maybe Text
a -> DescribeConnectionResponse
s {$sel:description:DescribeConnectionResponse' :: Maybe Text
description = Maybe Text
a} :: DescribeConnectionResponse)

-- | A time stamp for the time that the connection was last authorized.
describeConnectionResponse_lastAuthorizedTime :: Lens.Lens' DescribeConnectionResponse (Prelude.Maybe Prelude.UTCTime)
describeConnectionResponse_lastAuthorizedTime :: Lens' DescribeConnectionResponse (Maybe UTCTime)
describeConnectionResponse_lastAuthorizedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionResponse' {Maybe POSIX
lastAuthorizedTime :: Maybe POSIX
$sel:lastAuthorizedTime:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe POSIX
lastAuthorizedTime} -> Maybe POSIX
lastAuthorizedTime) (\s :: DescribeConnectionResponse
s@DescribeConnectionResponse' {} Maybe POSIX
a -> DescribeConnectionResponse
s {$sel:lastAuthorizedTime:DescribeConnectionResponse' :: Maybe POSIX
lastAuthorizedTime = Maybe POSIX
a} :: DescribeConnectionResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A time stamp for the time that the connection was last modified.
describeConnectionResponse_lastModifiedTime :: Lens.Lens' DescribeConnectionResponse (Prelude.Maybe Prelude.UTCTime)
describeConnectionResponse_lastModifiedTime :: Lens' DescribeConnectionResponse (Maybe UTCTime)
describeConnectionResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: DescribeConnectionResponse
s@DescribeConnectionResponse' {} Maybe POSIX
a -> DescribeConnectionResponse
s {$sel:lastModifiedTime:DescribeConnectionResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: DescribeConnectionResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The name of the connection retrieved.
describeConnectionResponse_name :: Lens.Lens' DescribeConnectionResponse (Prelude.Maybe Prelude.Text)
describeConnectionResponse_name :: Lens' DescribeConnectionResponse (Maybe Text)
describeConnectionResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionResponse' {Maybe Text
name :: Maybe Text
$sel:name:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: DescribeConnectionResponse
s@DescribeConnectionResponse' {} Maybe Text
a -> DescribeConnectionResponse
s {$sel:name:DescribeConnectionResponse' :: Maybe Text
name = Maybe Text
a} :: DescribeConnectionResponse)

-- | The ARN of the secret created from the authorization parameters
-- specified for the connection.
describeConnectionResponse_secretArn :: Lens.Lens' DescribeConnectionResponse (Prelude.Maybe Prelude.Text)
describeConnectionResponse_secretArn :: Lens' DescribeConnectionResponse (Maybe Text)
describeConnectionResponse_secretArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionResponse' {Maybe Text
secretArn :: Maybe Text
$sel:secretArn:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe Text
secretArn} -> Maybe Text
secretArn) (\s :: DescribeConnectionResponse
s@DescribeConnectionResponse' {} Maybe Text
a -> DescribeConnectionResponse
s {$sel:secretArn:DescribeConnectionResponse' :: Maybe Text
secretArn = Maybe Text
a} :: DescribeConnectionResponse)

-- | The reason that the connection is in the current connection state.
describeConnectionResponse_stateReason :: Lens.Lens' DescribeConnectionResponse (Prelude.Maybe Prelude.Text)
describeConnectionResponse_stateReason :: Lens' DescribeConnectionResponse (Maybe Text)
describeConnectionResponse_stateReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectionResponse' {Maybe Text
stateReason :: Maybe Text
$sel:stateReason:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe Text
stateReason} -> Maybe Text
stateReason) (\s :: DescribeConnectionResponse
s@DescribeConnectionResponse' {} Maybe Text
a -> DescribeConnectionResponse
s {$sel:stateReason:DescribeConnectionResponse' :: Maybe Text
stateReason = Maybe Text
a} :: DescribeConnectionResponse)

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

instance Prelude.NFData DescribeConnectionResponse where
  rnf :: DescribeConnectionResponse -> ()
rnf DescribeConnectionResponse' {Int
Maybe Text
Maybe POSIX
Maybe ConnectionAuthorizationType
Maybe ConnectionAuthResponseParameters
Maybe ConnectionState
httpStatus :: Int
stateReason :: Maybe Text
secretArn :: Maybe Text
name :: Maybe Text
lastModifiedTime :: Maybe POSIX
lastAuthorizedTime :: Maybe POSIX
description :: Maybe Text
creationTime :: Maybe POSIX
connectionState :: Maybe ConnectionState
connectionArn :: Maybe Text
authorizationType :: Maybe ConnectionAuthorizationType
authParameters :: Maybe ConnectionAuthResponseParameters
$sel:httpStatus:DescribeConnectionResponse' :: DescribeConnectionResponse -> Int
$sel:stateReason:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe Text
$sel:secretArn:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe Text
$sel:name:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe Text
$sel:lastModifiedTime:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe POSIX
$sel:lastAuthorizedTime:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe POSIX
$sel:description:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe Text
$sel:creationTime:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe POSIX
$sel:connectionState:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe ConnectionState
$sel:connectionArn:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe Text
$sel:authorizationType:DescribeConnectionResponse' :: DescribeConnectionResponse -> Maybe ConnectionAuthorizationType
$sel:authParameters:DescribeConnectionResponse' :: DescribeConnectionResponse
-> Maybe ConnectionAuthResponseParameters
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectionAuthResponseParameters
authParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectionAuthorizationType
authorizationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectionState
connectionState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastAuthorizedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
secretArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
stateReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus