{-# 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.EC2.TerminateClientVpnConnections
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Terminates active Client VPN endpoint connections. This action can be
-- used to terminate a specific client connection, or up to five
-- connections established by a specific user.
module Amazonka.EC2.TerminateClientVpnConnections
  ( -- * Creating a Request
    TerminateClientVpnConnections (..),
    newTerminateClientVpnConnections,

    -- * Request Lenses
    terminateClientVpnConnections_connectionId,
    terminateClientVpnConnections_dryRun,
    terminateClientVpnConnections_username,
    terminateClientVpnConnections_clientVpnEndpointId,

    -- * Destructuring the Response
    TerminateClientVpnConnectionsResponse (..),
    newTerminateClientVpnConnectionsResponse,

    -- * Response Lenses
    terminateClientVpnConnectionsResponse_clientVpnEndpointId,
    terminateClientVpnConnectionsResponse_connectionStatuses,
    terminateClientVpnConnectionsResponse_username,
    terminateClientVpnConnectionsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newTerminateClientVpnConnections' smart constructor.
data TerminateClientVpnConnections = TerminateClientVpnConnections'
  { -- | The ID of the client connection to be terminated.
    TerminateClientVpnConnections -> Maybe Text
connectionId :: Prelude.Maybe Prelude.Text,
    -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    TerminateClientVpnConnections -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The name of the user who initiated the connection. Use this option to
    -- terminate all active connections for the specified user. This option can
    -- only be used if the user has established up to five connections.
    TerminateClientVpnConnections -> Maybe Text
username :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Client VPN endpoint to which the client is connected.
    TerminateClientVpnConnections -> Text
clientVpnEndpointId :: Prelude.Text
  }
  deriving (TerminateClientVpnConnections
-> TerminateClientVpnConnections -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TerminateClientVpnConnections
-> TerminateClientVpnConnections -> Bool
$c/= :: TerminateClientVpnConnections
-> TerminateClientVpnConnections -> Bool
== :: TerminateClientVpnConnections
-> TerminateClientVpnConnections -> Bool
$c== :: TerminateClientVpnConnections
-> TerminateClientVpnConnections -> Bool
Prelude.Eq, ReadPrec [TerminateClientVpnConnections]
ReadPrec TerminateClientVpnConnections
Int -> ReadS TerminateClientVpnConnections
ReadS [TerminateClientVpnConnections]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TerminateClientVpnConnections]
$creadListPrec :: ReadPrec [TerminateClientVpnConnections]
readPrec :: ReadPrec TerminateClientVpnConnections
$creadPrec :: ReadPrec TerminateClientVpnConnections
readList :: ReadS [TerminateClientVpnConnections]
$creadList :: ReadS [TerminateClientVpnConnections]
readsPrec :: Int -> ReadS TerminateClientVpnConnections
$creadsPrec :: Int -> ReadS TerminateClientVpnConnections
Prelude.Read, Int -> TerminateClientVpnConnections -> ShowS
[TerminateClientVpnConnections] -> ShowS
TerminateClientVpnConnections -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TerminateClientVpnConnections] -> ShowS
$cshowList :: [TerminateClientVpnConnections] -> ShowS
show :: TerminateClientVpnConnections -> String
$cshow :: TerminateClientVpnConnections -> String
showsPrec :: Int -> TerminateClientVpnConnections -> ShowS
$cshowsPrec :: Int -> TerminateClientVpnConnections -> ShowS
Prelude.Show, forall x.
Rep TerminateClientVpnConnections x
-> TerminateClientVpnConnections
forall x.
TerminateClientVpnConnections
-> Rep TerminateClientVpnConnections x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep TerminateClientVpnConnections x
-> TerminateClientVpnConnections
$cfrom :: forall x.
TerminateClientVpnConnections
-> Rep TerminateClientVpnConnections x
Prelude.Generic)

-- |
-- Create a value of 'TerminateClientVpnConnections' 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:
--
-- 'connectionId', 'terminateClientVpnConnections_connectionId' - The ID of the client connection to be terminated.
--
-- 'dryRun', 'terminateClientVpnConnections_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'username', 'terminateClientVpnConnections_username' - The name of the user who initiated the connection. Use this option to
-- terminate all active connections for the specified user. This option can
-- only be used if the user has established up to five connections.
--
-- 'clientVpnEndpointId', 'terminateClientVpnConnections_clientVpnEndpointId' - The ID of the Client VPN endpoint to which the client is connected.
newTerminateClientVpnConnections ::
  -- | 'clientVpnEndpointId'
  Prelude.Text ->
  TerminateClientVpnConnections
newTerminateClientVpnConnections :: Text -> TerminateClientVpnConnections
newTerminateClientVpnConnections
  Text
pClientVpnEndpointId_ =
    TerminateClientVpnConnections'
      { $sel:connectionId:TerminateClientVpnConnections' :: Maybe Text
connectionId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:dryRun:TerminateClientVpnConnections' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
        $sel:username:TerminateClientVpnConnections' :: Maybe Text
username = forall a. Maybe a
Prelude.Nothing,
        $sel:clientVpnEndpointId:TerminateClientVpnConnections' :: Text
clientVpnEndpointId = Text
pClientVpnEndpointId_
      }

-- | The ID of the client connection to be terminated.
terminateClientVpnConnections_connectionId :: Lens.Lens' TerminateClientVpnConnections (Prelude.Maybe Prelude.Text)
terminateClientVpnConnections_connectionId :: Lens' TerminateClientVpnConnections (Maybe Text)
terminateClientVpnConnections_connectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TerminateClientVpnConnections' {Maybe Text
connectionId :: Maybe Text
$sel:connectionId:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Text
connectionId} -> Maybe Text
connectionId) (\s :: TerminateClientVpnConnections
s@TerminateClientVpnConnections' {} Maybe Text
a -> TerminateClientVpnConnections
s {$sel:connectionId:TerminateClientVpnConnections' :: Maybe Text
connectionId = Maybe Text
a} :: TerminateClientVpnConnections)

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
terminateClientVpnConnections_dryRun :: Lens.Lens' TerminateClientVpnConnections (Prelude.Maybe Prelude.Bool)
terminateClientVpnConnections_dryRun :: Lens' TerminateClientVpnConnections (Maybe Bool)
terminateClientVpnConnections_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TerminateClientVpnConnections' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: TerminateClientVpnConnections
s@TerminateClientVpnConnections' {} Maybe Bool
a -> TerminateClientVpnConnections
s {$sel:dryRun:TerminateClientVpnConnections' :: Maybe Bool
dryRun = Maybe Bool
a} :: TerminateClientVpnConnections)

-- | The name of the user who initiated the connection. Use this option to
-- terminate all active connections for the specified user. This option can
-- only be used if the user has established up to five connections.
terminateClientVpnConnections_username :: Lens.Lens' TerminateClientVpnConnections (Prelude.Maybe Prelude.Text)
terminateClientVpnConnections_username :: Lens' TerminateClientVpnConnections (Maybe Text)
terminateClientVpnConnections_username = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TerminateClientVpnConnections' {Maybe Text
username :: Maybe Text
$sel:username:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Text
username} -> Maybe Text
username) (\s :: TerminateClientVpnConnections
s@TerminateClientVpnConnections' {} Maybe Text
a -> TerminateClientVpnConnections
s {$sel:username:TerminateClientVpnConnections' :: Maybe Text
username = Maybe Text
a} :: TerminateClientVpnConnections)

-- | The ID of the Client VPN endpoint to which the client is connected.
terminateClientVpnConnections_clientVpnEndpointId :: Lens.Lens' TerminateClientVpnConnections Prelude.Text
terminateClientVpnConnections_clientVpnEndpointId :: Lens' TerminateClientVpnConnections Text
terminateClientVpnConnections_clientVpnEndpointId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TerminateClientVpnConnections' {Text
clientVpnEndpointId :: Text
$sel:clientVpnEndpointId:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Text
clientVpnEndpointId} -> Text
clientVpnEndpointId) (\s :: TerminateClientVpnConnections
s@TerminateClientVpnConnections' {} Text
a -> TerminateClientVpnConnections
s {$sel:clientVpnEndpointId:TerminateClientVpnConnections' :: Text
clientVpnEndpointId = Text
a} :: TerminateClientVpnConnections)

instance
  Core.AWSRequest
    TerminateClientVpnConnections
  where
  type
    AWSResponse TerminateClientVpnConnections =
      TerminateClientVpnConnectionsResponse
  request :: (Service -> Service)
-> TerminateClientVpnConnections
-> Request TerminateClientVpnConnections
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy TerminateClientVpnConnections
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse TerminateClientVpnConnections)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe [TerminateConnectionStatus]
-> Maybe Text
-> Int
-> TerminateClientVpnConnectionsResponse
TerminateClientVpnConnectionsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"clientVpnEndpointId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"connectionStatuses"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"username")
            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
    TerminateClientVpnConnections
  where
  hashWithSalt :: Int -> TerminateClientVpnConnections -> Int
hashWithSalt Int
_salt TerminateClientVpnConnections' {Maybe Bool
Maybe Text
Text
clientVpnEndpointId :: Text
username :: Maybe Text
dryRun :: Maybe Bool
connectionId :: Maybe Text
$sel:clientVpnEndpointId:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Text
$sel:username:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Text
$sel:dryRun:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Bool
$sel:connectionId:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
username
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientVpnEndpointId

instance Prelude.NFData TerminateClientVpnConnections where
  rnf :: TerminateClientVpnConnections -> ()
rnf TerminateClientVpnConnections' {Maybe Bool
Maybe Text
Text
clientVpnEndpointId :: Text
username :: Maybe Text
dryRun :: Maybe Bool
connectionId :: Maybe Text
$sel:clientVpnEndpointId:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Text
$sel:username:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Text
$sel:dryRun:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Bool
$sel:connectionId:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
username
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientVpnEndpointId

instance Data.ToHeaders TerminateClientVpnConnections where
  toHeaders :: TerminateClientVpnConnections -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery TerminateClientVpnConnections where
  toQuery :: TerminateClientVpnConnections -> QueryString
toQuery TerminateClientVpnConnections' {Maybe Bool
Maybe Text
Text
clientVpnEndpointId :: Text
username :: Maybe Text
dryRun :: Maybe Bool
connectionId :: Maybe Text
$sel:clientVpnEndpointId:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Text
$sel:username:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Text
$sel:dryRun:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Bool
$sel:connectionId:TerminateClientVpnConnections' :: TerminateClientVpnConnections -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"TerminateClientVpnConnections" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"ConnectionId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
connectionId,
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"Username" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
username,
        ByteString
"ClientVpnEndpointId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
clientVpnEndpointId
      ]

-- | /See:/ 'newTerminateClientVpnConnectionsResponse' smart constructor.
data TerminateClientVpnConnectionsResponse = TerminateClientVpnConnectionsResponse'
  { -- | The ID of the Client VPN endpoint.
    TerminateClientVpnConnectionsResponse -> Maybe Text
clientVpnEndpointId :: Prelude.Maybe Prelude.Text,
    -- | The current state of the client connections.
    TerminateClientVpnConnectionsResponse
-> Maybe [TerminateConnectionStatus]
connectionStatuses :: Prelude.Maybe [TerminateConnectionStatus],
    -- | The user who established the terminated client connections.
    TerminateClientVpnConnectionsResponse -> Maybe Text
username :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    TerminateClientVpnConnectionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (TerminateClientVpnConnectionsResponse
-> TerminateClientVpnConnectionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TerminateClientVpnConnectionsResponse
-> TerminateClientVpnConnectionsResponse -> Bool
$c/= :: TerminateClientVpnConnectionsResponse
-> TerminateClientVpnConnectionsResponse -> Bool
== :: TerminateClientVpnConnectionsResponse
-> TerminateClientVpnConnectionsResponse -> Bool
$c== :: TerminateClientVpnConnectionsResponse
-> TerminateClientVpnConnectionsResponse -> Bool
Prelude.Eq, ReadPrec [TerminateClientVpnConnectionsResponse]
ReadPrec TerminateClientVpnConnectionsResponse
Int -> ReadS TerminateClientVpnConnectionsResponse
ReadS [TerminateClientVpnConnectionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TerminateClientVpnConnectionsResponse]
$creadListPrec :: ReadPrec [TerminateClientVpnConnectionsResponse]
readPrec :: ReadPrec TerminateClientVpnConnectionsResponse
$creadPrec :: ReadPrec TerminateClientVpnConnectionsResponse
readList :: ReadS [TerminateClientVpnConnectionsResponse]
$creadList :: ReadS [TerminateClientVpnConnectionsResponse]
readsPrec :: Int -> ReadS TerminateClientVpnConnectionsResponse
$creadsPrec :: Int -> ReadS TerminateClientVpnConnectionsResponse
Prelude.Read, Int -> TerminateClientVpnConnectionsResponse -> ShowS
[TerminateClientVpnConnectionsResponse] -> ShowS
TerminateClientVpnConnectionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TerminateClientVpnConnectionsResponse] -> ShowS
$cshowList :: [TerminateClientVpnConnectionsResponse] -> ShowS
show :: TerminateClientVpnConnectionsResponse -> String
$cshow :: TerminateClientVpnConnectionsResponse -> String
showsPrec :: Int -> TerminateClientVpnConnectionsResponse -> ShowS
$cshowsPrec :: Int -> TerminateClientVpnConnectionsResponse -> ShowS
Prelude.Show, forall x.
Rep TerminateClientVpnConnectionsResponse x
-> TerminateClientVpnConnectionsResponse
forall x.
TerminateClientVpnConnectionsResponse
-> Rep TerminateClientVpnConnectionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep TerminateClientVpnConnectionsResponse x
-> TerminateClientVpnConnectionsResponse
$cfrom :: forall x.
TerminateClientVpnConnectionsResponse
-> Rep TerminateClientVpnConnectionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'TerminateClientVpnConnectionsResponse' 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:
--
-- 'clientVpnEndpointId', 'terminateClientVpnConnectionsResponse_clientVpnEndpointId' - The ID of the Client VPN endpoint.
--
-- 'connectionStatuses', 'terminateClientVpnConnectionsResponse_connectionStatuses' - The current state of the client connections.
--
-- 'username', 'terminateClientVpnConnectionsResponse_username' - The user who established the terminated client connections.
--
-- 'httpStatus', 'terminateClientVpnConnectionsResponse_httpStatus' - The response's http status code.
newTerminateClientVpnConnectionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  TerminateClientVpnConnectionsResponse
newTerminateClientVpnConnectionsResponse :: Int -> TerminateClientVpnConnectionsResponse
newTerminateClientVpnConnectionsResponse Int
pHttpStatus_ =
  TerminateClientVpnConnectionsResponse'
    { $sel:clientVpnEndpointId:TerminateClientVpnConnectionsResponse' :: Maybe Text
clientVpnEndpointId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:connectionStatuses:TerminateClientVpnConnectionsResponse' :: Maybe [TerminateConnectionStatus]
connectionStatuses = forall a. Maybe a
Prelude.Nothing,
      $sel:username:TerminateClientVpnConnectionsResponse' :: Maybe Text
username = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:TerminateClientVpnConnectionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID of the Client VPN endpoint.
terminateClientVpnConnectionsResponse_clientVpnEndpointId :: Lens.Lens' TerminateClientVpnConnectionsResponse (Prelude.Maybe Prelude.Text)
terminateClientVpnConnectionsResponse_clientVpnEndpointId :: Lens' TerminateClientVpnConnectionsResponse (Maybe Text)
terminateClientVpnConnectionsResponse_clientVpnEndpointId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TerminateClientVpnConnectionsResponse' {Maybe Text
clientVpnEndpointId :: Maybe Text
$sel:clientVpnEndpointId:TerminateClientVpnConnectionsResponse' :: TerminateClientVpnConnectionsResponse -> Maybe Text
clientVpnEndpointId} -> Maybe Text
clientVpnEndpointId) (\s :: TerminateClientVpnConnectionsResponse
s@TerminateClientVpnConnectionsResponse' {} Maybe Text
a -> TerminateClientVpnConnectionsResponse
s {$sel:clientVpnEndpointId:TerminateClientVpnConnectionsResponse' :: Maybe Text
clientVpnEndpointId = Maybe Text
a} :: TerminateClientVpnConnectionsResponse)

-- | The current state of the client connections.
terminateClientVpnConnectionsResponse_connectionStatuses :: Lens.Lens' TerminateClientVpnConnectionsResponse (Prelude.Maybe [TerminateConnectionStatus])
terminateClientVpnConnectionsResponse_connectionStatuses :: Lens'
  TerminateClientVpnConnectionsResponse
  (Maybe [TerminateConnectionStatus])
terminateClientVpnConnectionsResponse_connectionStatuses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TerminateClientVpnConnectionsResponse' {Maybe [TerminateConnectionStatus]
connectionStatuses :: Maybe [TerminateConnectionStatus]
$sel:connectionStatuses:TerminateClientVpnConnectionsResponse' :: TerminateClientVpnConnectionsResponse
-> Maybe [TerminateConnectionStatus]
connectionStatuses} -> Maybe [TerminateConnectionStatus]
connectionStatuses) (\s :: TerminateClientVpnConnectionsResponse
s@TerminateClientVpnConnectionsResponse' {} Maybe [TerminateConnectionStatus]
a -> TerminateClientVpnConnectionsResponse
s {$sel:connectionStatuses:TerminateClientVpnConnectionsResponse' :: Maybe [TerminateConnectionStatus]
connectionStatuses = Maybe [TerminateConnectionStatus]
a} :: TerminateClientVpnConnectionsResponse) 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

-- | The user who established the terminated client connections.
terminateClientVpnConnectionsResponse_username :: Lens.Lens' TerminateClientVpnConnectionsResponse (Prelude.Maybe Prelude.Text)
terminateClientVpnConnectionsResponse_username :: Lens' TerminateClientVpnConnectionsResponse (Maybe Text)
terminateClientVpnConnectionsResponse_username = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TerminateClientVpnConnectionsResponse' {Maybe Text
username :: Maybe Text
$sel:username:TerminateClientVpnConnectionsResponse' :: TerminateClientVpnConnectionsResponse -> Maybe Text
username} -> Maybe Text
username) (\s :: TerminateClientVpnConnectionsResponse
s@TerminateClientVpnConnectionsResponse' {} Maybe Text
a -> TerminateClientVpnConnectionsResponse
s {$sel:username:TerminateClientVpnConnectionsResponse' :: Maybe Text
username = Maybe Text
a} :: TerminateClientVpnConnectionsResponse)

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

instance
  Prelude.NFData
    TerminateClientVpnConnectionsResponse
  where
  rnf :: TerminateClientVpnConnectionsResponse -> ()
rnf TerminateClientVpnConnectionsResponse' {Int
Maybe [TerminateConnectionStatus]
Maybe Text
httpStatus :: Int
username :: Maybe Text
connectionStatuses :: Maybe [TerminateConnectionStatus]
clientVpnEndpointId :: Maybe Text
$sel:httpStatus:TerminateClientVpnConnectionsResponse' :: TerminateClientVpnConnectionsResponse -> Int
$sel:username:TerminateClientVpnConnectionsResponse' :: TerminateClientVpnConnectionsResponse -> Maybe Text
$sel:connectionStatuses:TerminateClientVpnConnectionsResponse' :: TerminateClientVpnConnectionsResponse
-> Maybe [TerminateConnectionStatus]
$sel:clientVpnEndpointId:TerminateClientVpnConnectionsResponse' :: TerminateClientVpnConnectionsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientVpnEndpointId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [TerminateConnectionStatus]
connectionStatuses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
username
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus