{-# 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.DeauthorizeConnection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes all authorization parameters from the connection. This lets you
-- remove the secret from the connection so you can reuse it without having
-- to create a new connection.
module Amazonka.CloudWatchEvents.DeauthorizeConnection
  ( -- * Creating a Request
    DeauthorizeConnection (..),
    newDeauthorizeConnection,

    -- * Request Lenses
    deauthorizeConnection_name,

    -- * Destructuring the Response
    DeauthorizeConnectionResponse (..),
    newDeauthorizeConnectionResponse,

    -- * Response Lenses
    deauthorizeConnectionResponse_connectionArn,
    deauthorizeConnectionResponse_connectionState,
    deauthorizeConnectionResponse_creationTime,
    deauthorizeConnectionResponse_lastAuthorizedTime,
    deauthorizeConnectionResponse_lastModifiedTime,
    deauthorizeConnectionResponse_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:/ 'newDeauthorizeConnection' smart constructor.
data DeauthorizeConnection = DeauthorizeConnection'
  { -- | The name of the connection to remove authorization from.
    DeauthorizeConnection -> Text
name :: Prelude.Text
  }
  deriving (DeauthorizeConnection -> DeauthorizeConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeauthorizeConnection -> DeauthorizeConnection -> Bool
$c/= :: DeauthorizeConnection -> DeauthorizeConnection -> Bool
== :: DeauthorizeConnection -> DeauthorizeConnection -> Bool
$c== :: DeauthorizeConnection -> DeauthorizeConnection -> Bool
Prelude.Eq, ReadPrec [DeauthorizeConnection]
ReadPrec DeauthorizeConnection
Int -> ReadS DeauthorizeConnection
ReadS [DeauthorizeConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeauthorizeConnection]
$creadListPrec :: ReadPrec [DeauthorizeConnection]
readPrec :: ReadPrec DeauthorizeConnection
$creadPrec :: ReadPrec DeauthorizeConnection
readList :: ReadS [DeauthorizeConnection]
$creadList :: ReadS [DeauthorizeConnection]
readsPrec :: Int -> ReadS DeauthorizeConnection
$creadsPrec :: Int -> ReadS DeauthorizeConnection
Prelude.Read, Int -> DeauthorizeConnection -> ShowS
[DeauthorizeConnection] -> ShowS
DeauthorizeConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeauthorizeConnection] -> ShowS
$cshowList :: [DeauthorizeConnection] -> ShowS
show :: DeauthorizeConnection -> String
$cshow :: DeauthorizeConnection -> String
showsPrec :: Int -> DeauthorizeConnection -> ShowS
$cshowsPrec :: Int -> DeauthorizeConnection -> ShowS
Prelude.Show, forall x. Rep DeauthorizeConnection x -> DeauthorizeConnection
forall x. DeauthorizeConnection -> Rep DeauthorizeConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeauthorizeConnection x -> DeauthorizeConnection
$cfrom :: forall x. DeauthorizeConnection -> Rep DeauthorizeConnection x
Prelude.Generic)

-- |
-- Create a value of 'DeauthorizeConnection' 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', 'deauthorizeConnection_name' - The name of the connection to remove authorization from.
newDeauthorizeConnection ::
  -- | 'name'
  Prelude.Text ->
  DeauthorizeConnection
newDeauthorizeConnection :: Text -> DeauthorizeConnection
newDeauthorizeConnection Text
pName_ =
  DeauthorizeConnection' {$sel:name:DeauthorizeConnection' :: Text
name = Text
pName_}

-- | The name of the connection to remove authorization from.
deauthorizeConnection_name :: Lens.Lens' DeauthorizeConnection Prelude.Text
deauthorizeConnection_name :: Lens' DeauthorizeConnection Text
deauthorizeConnection_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeauthorizeConnection' {Text
name :: Text
$sel:name:DeauthorizeConnection' :: DeauthorizeConnection -> Text
name} -> Text
name) (\s :: DeauthorizeConnection
s@DeauthorizeConnection' {} Text
a -> DeauthorizeConnection
s {$sel:name:DeauthorizeConnection' :: Text
name = Text
a} :: DeauthorizeConnection)

instance Core.AWSRequest DeauthorizeConnection where
  type
    AWSResponse DeauthorizeConnection =
      DeauthorizeConnectionResponse
  request :: (Service -> Service)
-> DeauthorizeConnection -> Request DeauthorizeConnection
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 DeauthorizeConnection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeauthorizeConnection)))
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 Text
-> Maybe ConnectionState
-> Maybe POSIX
-> Maybe POSIX
-> Maybe POSIX
-> Int
-> DeauthorizeConnectionResponse
DeauthorizeConnectionResponse'
            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
"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
"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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DeauthorizeConnection where
  hashWithSalt :: Int -> DeauthorizeConnection -> Int
hashWithSalt Int
_salt DeauthorizeConnection' {Text
name :: Text
$sel:name:DeauthorizeConnection' :: DeauthorizeConnection -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders DeauthorizeConnection where
  toHeaders :: DeauthorizeConnection -> 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.DeauthorizeConnection" ::
                          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 DeauthorizeConnection where
  toJSON :: DeauthorizeConnection -> Value
toJSON DeauthorizeConnection' {Text
name :: Text
$sel:name:DeauthorizeConnection' :: DeauthorizeConnection -> 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 DeauthorizeConnection where
  toPath :: DeauthorizeConnection -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDeauthorizeConnectionResponse' smart constructor.
data DeauthorizeConnectionResponse = DeauthorizeConnectionResponse'
  { -- | The ARN of the connection that authorization was removed from.
    DeauthorizeConnectionResponse -> Maybe Text
connectionArn :: Prelude.Maybe Prelude.Text,
    -- | The state of the connection.
    DeauthorizeConnectionResponse -> Maybe ConnectionState
connectionState :: Prelude.Maybe ConnectionState,
    -- | A time stamp for the time that the connection was created.
    DeauthorizeConnectionResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | A time stamp for the time that the connection was last authorized.
    DeauthorizeConnectionResponse -> Maybe POSIX
lastAuthorizedTime :: Prelude.Maybe Data.POSIX,
    -- | A time stamp for the time that the connection was last updated.
    DeauthorizeConnectionResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The response's http status code.
    DeauthorizeConnectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeauthorizeConnectionResponse
-> DeauthorizeConnectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeauthorizeConnectionResponse
-> DeauthorizeConnectionResponse -> Bool
$c/= :: DeauthorizeConnectionResponse
-> DeauthorizeConnectionResponse -> Bool
== :: DeauthorizeConnectionResponse
-> DeauthorizeConnectionResponse -> Bool
$c== :: DeauthorizeConnectionResponse
-> DeauthorizeConnectionResponse -> Bool
Prelude.Eq, ReadPrec [DeauthorizeConnectionResponse]
ReadPrec DeauthorizeConnectionResponse
Int -> ReadS DeauthorizeConnectionResponse
ReadS [DeauthorizeConnectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeauthorizeConnectionResponse]
$creadListPrec :: ReadPrec [DeauthorizeConnectionResponse]
readPrec :: ReadPrec DeauthorizeConnectionResponse
$creadPrec :: ReadPrec DeauthorizeConnectionResponse
readList :: ReadS [DeauthorizeConnectionResponse]
$creadList :: ReadS [DeauthorizeConnectionResponse]
readsPrec :: Int -> ReadS DeauthorizeConnectionResponse
$creadsPrec :: Int -> ReadS DeauthorizeConnectionResponse
Prelude.Read, Int -> DeauthorizeConnectionResponse -> ShowS
[DeauthorizeConnectionResponse] -> ShowS
DeauthorizeConnectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeauthorizeConnectionResponse] -> ShowS
$cshowList :: [DeauthorizeConnectionResponse] -> ShowS
show :: DeauthorizeConnectionResponse -> String
$cshow :: DeauthorizeConnectionResponse -> String
showsPrec :: Int -> DeauthorizeConnectionResponse -> ShowS
$cshowsPrec :: Int -> DeauthorizeConnectionResponse -> ShowS
Prelude.Show, forall x.
Rep DeauthorizeConnectionResponse x
-> DeauthorizeConnectionResponse
forall x.
DeauthorizeConnectionResponse
-> Rep DeauthorizeConnectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeauthorizeConnectionResponse x
-> DeauthorizeConnectionResponse
$cfrom :: forall x.
DeauthorizeConnectionResponse
-> Rep DeauthorizeConnectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeauthorizeConnectionResponse' 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:
--
-- 'connectionArn', 'deauthorizeConnectionResponse_connectionArn' - The ARN of the connection that authorization was removed from.
--
-- 'connectionState', 'deauthorizeConnectionResponse_connectionState' - The state of the connection.
--
-- 'creationTime', 'deauthorizeConnectionResponse_creationTime' - A time stamp for the time that the connection was created.
--
-- 'lastAuthorizedTime', 'deauthorizeConnectionResponse_lastAuthorizedTime' - A time stamp for the time that the connection was last authorized.
--
-- 'lastModifiedTime', 'deauthorizeConnectionResponse_lastModifiedTime' - A time stamp for the time that the connection was last updated.
--
-- 'httpStatus', 'deauthorizeConnectionResponse_httpStatus' - The response's http status code.
newDeauthorizeConnectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeauthorizeConnectionResponse
newDeauthorizeConnectionResponse :: Int -> DeauthorizeConnectionResponse
newDeauthorizeConnectionResponse Int
pHttpStatus_ =
  DeauthorizeConnectionResponse'
    { $sel:connectionArn:DeauthorizeConnectionResponse' :: Maybe Text
connectionArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:connectionState:DeauthorizeConnectionResponse' :: Maybe ConnectionState
connectionState = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:DeauthorizeConnectionResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:lastAuthorizedTime:DeauthorizeConnectionResponse' :: Maybe POSIX
lastAuthorizedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:DeauthorizeConnectionResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeauthorizeConnectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the connection that authorization was removed from.
deauthorizeConnectionResponse_connectionArn :: Lens.Lens' DeauthorizeConnectionResponse (Prelude.Maybe Prelude.Text)
deauthorizeConnectionResponse_connectionArn :: Lens' DeauthorizeConnectionResponse (Maybe Text)
deauthorizeConnectionResponse_connectionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeauthorizeConnectionResponse' {Maybe Text
connectionArn :: Maybe Text
$sel:connectionArn:DeauthorizeConnectionResponse' :: DeauthorizeConnectionResponse -> Maybe Text
connectionArn} -> Maybe Text
connectionArn) (\s :: DeauthorizeConnectionResponse
s@DeauthorizeConnectionResponse' {} Maybe Text
a -> DeauthorizeConnectionResponse
s {$sel:connectionArn:DeauthorizeConnectionResponse' :: Maybe Text
connectionArn = Maybe Text
a} :: DeauthorizeConnectionResponse)

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

-- | A time stamp for the time that the connection was created.
deauthorizeConnectionResponse_creationTime :: Lens.Lens' DeauthorizeConnectionResponse (Prelude.Maybe Prelude.UTCTime)
deauthorizeConnectionResponse_creationTime :: Lens' DeauthorizeConnectionResponse (Maybe UTCTime)
deauthorizeConnectionResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeauthorizeConnectionResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DeauthorizeConnectionResponse' :: DeauthorizeConnectionResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DeauthorizeConnectionResponse
s@DeauthorizeConnectionResponse' {} Maybe POSIX
a -> DeauthorizeConnectionResponse
s {$sel:creationTime:DeauthorizeConnectionResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DeauthorizeConnectionResponse) 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 authorized.
deauthorizeConnectionResponse_lastAuthorizedTime :: Lens.Lens' DeauthorizeConnectionResponse (Prelude.Maybe Prelude.UTCTime)
deauthorizeConnectionResponse_lastAuthorizedTime :: Lens' DeauthorizeConnectionResponse (Maybe UTCTime)
deauthorizeConnectionResponse_lastAuthorizedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeauthorizeConnectionResponse' {Maybe POSIX
lastAuthorizedTime :: Maybe POSIX
$sel:lastAuthorizedTime:DeauthorizeConnectionResponse' :: DeauthorizeConnectionResponse -> Maybe POSIX
lastAuthorizedTime} -> Maybe POSIX
lastAuthorizedTime) (\s :: DeauthorizeConnectionResponse
s@DeauthorizeConnectionResponse' {} Maybe POSIX
a -> DeauthorizeConnectionResponse
s {$sel:lastAuthorizedTime:DeauthorizeConnectionResponse' :: Maybe POSIX
lastAuthorizedTime = Maybe POSIX
a} :: DeauthorizeConnectionResponse) 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 updated.
deauthorizeConnectionResponse_lastModifiedTime :: Lens.Lens' DeauthorizeConnectionResponse (Prelude.Maybe Prelude.UTCTime)
deauthorizeConnectionResponse_lastModifiedTime :: Lens' DeauthorizeConnectionResponse (Maybe UTCTime)
deauthorizeConnectionResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeauthorizeConnectionResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:DeauthorizeConnectionResponse' :: DeauthorizeConnectionResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: DeauthorizeConnectionResponse
s@DeauthorizeConnectionResponse' {} Maybe POSIX
a -> DeauthorizeConnectionResponse
s {$sel:lastModifiedTime:DeauthorizeConnectionResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: DeauthorizeConnectionResponse) 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 response's http status code.
deauthorizeConnectionResponse_httpStatus :: Lens.Lens' DeauthorizeConnectionResponse Prelude.Int
deauthorizeConnectionResponse_httpStatus :: Lens' DeauthorizeConnectionResponse Int
deauthorizeConnectionResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeauthorizeConnectionResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeauthorizeConnectionResponse' :: DeauthorizeConnectionResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeauthorizeConnectionResponse
s@DeauthorizeConnectionResponse' {} Int
a -> DeauthorizeConnectionResponse
s {$sel:httpStatus:DeauthorizeConnectionResponse' :: Int
httpStatus = Int
a} :: DeauthorizeConnectionResponse)

instance Prelude.NFData DeauthorizeConnectionResponse where
  rnf :: DeauthorizeConnectionResponse -> ()
rnf DeauthorizeConnectionResponse' {Int
Maybe Text
Maybe POSIX
Maybe ConnectionState
httpStatus :: Int
lastModifiedTime :: Maybe POSIX
lastAuthorizedTime :: Maybe POSIX
creationTime :: Maybe POSIX
connectionState :: Maybe ConnectionState
connectionArn :: Maybe Text
$sel:httpStatus:DeauthorizeConnectionResponse' :: DeauthorizeConnectionResponse -> Int
$sel:lastModifiedTime:DeauthorizeConnectionResponse' :: DeauthorizeConnectionResponse -> Maybe POSIX
$sel:lastAuthorizedTime:DeauthorizeConnectionResponse' :: DeauthorizeConnectionResponse -> Maybe POSIX
$sel:creationTime:DeauthorizeConnectionResponse' :: DeauthorizeConnectionResponse -> Maybe POSIX
$sel:connectionState:DeauthorizeConnectionResponse' :: DeauthorizeConnectionResponse -> Maybe ConnectionState
$sel:connectionArn:DeauthorizeConnectionResponse' :: DeauthorizeConnectionResponse -> Maybe Text
..} =
    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 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 Int
httpStatus