{-# 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.ApplySecurityGroupsToClientVpnTargetNetwork
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Applies a security group to the association between the target network
-- and the Client VPN endpoint. This action replaces the existing security
-- groups with the specified security groups.
module Amazonka.EC2.ApplySecurityGroupsToClientVpnTargetNetwork
  ( -- * Creating a Request
    ApplySecurityGroupsToClientVpnTargetNetwork (..),
    newApplySecurityGroupsToClientVpnTargetNetwork,

    -- * Request Lenses
    applySecurityGroupsToClientVpnTargetNetwork_dryRun,
    applySecurityGroupsToClientVpnTargetNetwork_clientVpnEndpointId,
    applySecurityGroupsToClientVpnTargetNetwork_vpcId,
    applySecurityGroupsToClientVpnTargetNetwork_securityGroupIds,

    -- * Destructuring the Response
    ApplySecurityGroupsToClientVpnTargetNetworkResponse (..),
    newApplySecurityGroupsToClientVpnTargetNetworkResponse,

    -- * Response Lenses
    applySecurityGroupsToClientVpnTargetNetworkResponse_securityGroupIds,
    applySecurityGroupsToClientVpnTargetNetworkResponse_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:/ 'newApplySecurityGroupsToClientVpnTargetNetwork' smart constructor.
data ApplySecurityGroupsToClientVpnTargetNetwork = ApplySecurityGroupsToClientVpnTargetNetwork'
  { -- | 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@.
    ApplySecurityGroupsToClientVpnTargetNetwork -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the Client VPN endpoint.
    ApplySecurityGroupsToClientVpnTargetNetwork -> Text
clientVpnEndpointId :: Prelude.Text,
    -- | The ID of the VPC in which the associated target network is located.
    ApplySecurityGroupsToClientVpnTargetNetwork -> Text
vpcId :: Prelude.Text,
    -- | The IDs of the security groups to apply to the associated target
    -- network. Up to 5 security groups can be applied to an associated target
    -- network.
    ApplySecurityGroupsToClientVpnTargetNetwork -> [Text]
securityGroupIds :: [Prelude.Text]
  }
  deriving (ApplySecurityGroupsToClientVpnTargetNetwork
-> ApplySecurityGroupsToClientVpnTargetNetwork -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplySecurityGroupsToClientVpnTargetNetwork
-> ApplySecurityGroupsToClientVpnTargetNetwork -> Bool
$c/= :: ApplySecurityGroupsToClientVpnTargetNetwork
-> ApplySecurityGroupsToClientVpnTargetNetwork -> Bool
== :: ApplySecurityGroupsToClientVpnTargetNetwork
-> ApplySecurityGroupsToClientVpnTargetNetwork -> Bool
$c== :: ApplySecurityGroupsToClientVpnTargetNetwork
-> ApplySecurityGroupsToClientVpnTargetNetwork -> Bool
Prelude.Eq, ReadPrec [ApplySecurityGroupsToClientVpnTargetNetwork]
ReadPrec ApplySecurityGroupsToClientVpnTargetNetwork
Int -> ReadS ApplySecurityGroupsToClientVpnTargetNetwork
ReadS [ApplySecurityGroupsToClientVpnTargetNetwork]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplySecurityGroupsToClientVpnTargetNetwork]
$creadListPrec :: ReadPrec [ApplySecurityGroupsToClientVpnTargetNetwork]
readPrec :: ReadPrec ApplySecurityGroupsToClientVpnTargetNetwork
$creadPrec :: ReadPrec ApplySecurityGroupsToClientVpnTargetNetwork
readList :: ReadS [ApplySecurityGroupsToClientVpnTargetNetwork]
$creadList :: ReadS [ApplySecurityGroupsToClientVpnTargetNetwork]
readsPrec :: Int -> ReadS ApplySecurityGroupsToClientVpnTargetNetwork
$creadsPrec :: Int -> ReadS ApplySecurityGroupsToClientVpnTargetNetwork
Prelude.Read, Int -> ApplySecurityGroupsToClientVpnTargetNetwork -> ShowS
[ApplySecurityGroupsToClientVpnTargetNetwork] -> ShowS
ApplySecurityGroupsToClientVpnTargetNetwork -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplySecurityGroupsToClientVpnTargetNetwork] -> ShowS
$cshowList :: [ApplySecurityGroupsToClientVpnTargetNetwork] -> ShowS
show :: ApplySecurityGroupsToClientVpnTargetNetwork -> String
$cshow :: ApplySecurityGroupsToClientVpnTargetNetwork -> String
showsPrec :: Int -> ApplySecurityGroupsToClientVpnTargetNetwork -> ShowS
$cshowsPrec :: Int -> ApplySecurityGroupsToClientVpnTargetNetwork -> ShowS
Prelude.Show, forall x.
Rep ApplySecurityGroupsToClientVpnTargetNetwork x
-> ApplySecurityGroupsToClientVpnTargetNetwork
forall x.
ApplySecurityGroupsToClientVpnTargetNetwork
-> Rep ApplySecurityGroupsToClientVpnTargetNetwork x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ApplySecurityGroupsToClientVpnTargetNetwork x
-> ApplySecurityGroupsToClientVpnTargetNetwork
$cfrom :: forall x.
ApplySecurityGroupsToClientVpnTargetNetwork
-> Rep ApplySecurityGroupsToClientVpnTargetNetwork x
Prelude.Generic)

-- |
-- Create a value of 'ApplySecurityGroupsToClientVpnTargetNetwork' 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:
--
-- 'dryRun', 'applySecurityGroupsToClientVpnTargetNetwork_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@.
--
-- 'clientVpnEndpointId', 'applySecurityGroupsToClientVpnTargetNetwork_clientVpnEndpointId' - The ID of the Client VPN endpoint.
--
-- 'vpcId', 'applySecurityGroupsToClientVpnTargetNetwork_vpcId' - The ID of the VPC in which the associated target network is located.
--
-- 'securityGroupIds', 'applySecurityGroupsToClientVpnTargetNetwork_securityGroupIds' - The IDs of the security groups to apply to the associated target
-- network. Up to 5 security groups can be applied to an associated target
-- network.
newApplySecurityGroupsToClientVpnTargetNetwork ::
  -- | 'clientVpnEndpointId'
  Prelude.Text ->
  -- | 'vpcId'
  Prelude.Text ->
  ApplySecurityGroupsToClientVpnTargetNetwork
newApplySecurityGroupsToClientVpnTargetNetwork :: Text -> Text -> ApplySecurityGroupsToClientVpnTargetNetwork
newApplySecurityGroupsToClientVpnTargetNetwork
  Text
pClientVpnEndpointId_
  Text
pVpcId_ =
    ApplySecurityGroupsToClientVpnTargetNetwork'
      { $sel:dryRun:ApplySecurityGroupsToClientVpnTargetNetwork' :: Maybe Bool
dryRun =
          forall a. Maybe a
Prelude.Nothing,
        $sel:clientVpnEndpointId:ApplySecurityGroupsToClientVpnTargetNetwork' :: Text
clientVpnEndpointId =
          Text
pClientVpnEndpointId_,
        $sel:vpcId:ApplySecurityGroupsToClientVpnTargetNetwork' :: Text
vpcId = Text
pVpcId_,
        $sel:securityGroupIds:ApplySecurityGroupsToClientVpnTargetNetwork' :: [Text]
securityGroupIds =
          forall a. Monoid a => a
Prelude.mempty
      }

-- | 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@.
applySecurityGroupsToClientVpnTargetNetwork_dryRun :: Lens.Lens' ApplySecurityGroupsToClientVpnTargetNetwork (Prelude.Maybe Prelude.Bool)
applySecurityGroupsToClientVpnTargetNetwork_dryRun :: Lens' ApplySecurityGroupsToClientVpnTargetNetwork (Maybe Bool)
applySecurityGroupsToClientVpnTargetNetwork_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ApplySecurityGroupsToClientVpnTargetNetwork' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: ApplySecurityGroupsToClientVpnTargetNetwork
s@ApplySecurityGroupsToClientVpnTargetNetwork' {} Maybe Bool
a -> ApplySecurityGroupsToClientVpnTargetNetwork
s {$sel:dryRun:ApplySecurityGroupsToClientVpnTargetNetwork' :: Maybe Bool
dryRun = Maybe Bool
a} :: ApplySecurityGroupsToClientVpnTargetNetwork)

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

-- | The ID of the VPC in which the associated target network is located.
applySecurityGroupsToClientVpnTargetNetwork_vpcId :: Lens.Lens' ApplySecurityGroupsToClientVpnTargetNetwork Prelude.Text
applySecurityGroupsToClientVpnTargetNetwork_vpcId :: Lens' ApplySecurityGroupsToClientVpnTargetNetwork Text
applySecurityGroupsToClientVpnTargetNetwork_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ApplySecurityGroupsToClientVpnTargetNetwork' {Text
vpcId :: Text
$sel:vpcId:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> Text
vpcId} -> Text
vpcId) (\s :: ApplySecurityGroupsToClientVpnTargetNetwork
s@ApplySecurityGroupsToClientVpnTargetNetwork' {} Text
a -> ApplySecurityGroupsToClientVpnTargetNetwork
s {$sel:vpcId:ApplySecurityGroupsToClientVpnTargetNetwork' :: Text
vpcId = Text
a} :: ApplySecurityGroupsToClientVpnTargetNetwork)

-- | The IDs of the security groups to apply to the associated target
-- network. Up to 5 security groups can be applied to an associated target
-- network.
applySecurityGroupsToClientVpnTargetNetwork_securityGroupIds :: Lens.Lens' ApplySecurityGroupsToClientVpnTargetNetwork [Prelude.Text]
applySecurityGroupsToClientVpnTargetNetwork_securityGroupIds :: Lens' ApplySecurityGroupsToClientVpnTargetNetwork [Text]
applySecurityGroupsToClientVpnTargetNetwork_securityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ApplySecurityGroupsToClientVpnTargetNetwork' {[Text]
securityGroupIds :: [Text]
$sel:securityGroupIds:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> [Text]
securityGroupIds} -> [Text]
securityGroupIds) (\s :: ApplySecurityGroupsToClientVpnTargetNetwork
s@ApplySecurityGroupsToClientVpnTargetNetwork' {} [Text]
a -> ApplySecurityGroupsToClientVpnTargetNetwork
s {$sel:securityGroupIds:ApplySecurityGroupsToClientVpnTargetNetwork' :: [Text]
securityGroupIds = [Text]
a} :: ApplySecurityGroupsToClientVpnTargetNetwork) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance
  Prelude.Hashable
    ApplySecurityGroupsToClientVpnTargetNetwork
  where
  hashWithSalt :: Int -> ApplySecurityGroupsToClientVpnTargetNetwork -> Int
hashWithSalt
    Int
_salt
    ApplySecurityGroupsToClientVpnTargetNetwork' {[Text]
Maybe Bool
Text
securityGroupIds :: [Text]
vpcId :: Text
clientVpnEndpointId :: Text
dryRun :: Maybe Bool
$sel:securityGroupIds:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> [Text]
$sel:vpcId:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> Text
$sel:clientVpnEndpointId:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> Text
$sel:dryRun:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> Maybe Bool
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientVpnEndpointId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vpcId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
securityGroupIds

instance
  Prelude.NFData
    ApplySecurityGroupsToClientVpnTargetNetwork
  where
  rnf :: ApplySecurityGroupsToClientVpnTargetNetwork -> ()
rnf ApplySecurityGroupsToClientVpnTargetNetwork' {[Text]
Maybe Bool
Text
securityGroupIds :: [Text]
vpcId :: Text
clientVpnEndpointId :: Text
dryRun :: Maybe Bool
$sel:securityGroupIds:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> [Text]
$sel:vpcId:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> Text
$sel:clientVpnEndpointId:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> Text
$sel:dryRun:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> Maybe Bool
..} =
    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 Text
clientVpnEndpointId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vpcId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
securityGroupIds

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

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

instance
  Data.ToQuery
    ApplySecurityGroupsToClientVpnTargetNetwork
  where
  toQuery :: ApplySecurityGroupsToClientVpnTargetNetwork -> QueryString
toQuery
    ApplySecurityGroupsToClientVpnTargetNetwork' {[Text]
Maybe Bool
Text
securityGroupIds :: [Text]
vpcId :: Text
clientVpnEndpointId :: Text
dryRun :: Maybe Bool
$sel:securityGroupIds:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> [Text]
$sel:vpcId:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> Text
$sel:clientVpnEndpointId:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> Text
$sel:dryRun:ApplySecurityGroupsToClientVpnTargetNetwork' :: ApplySecurityGroupsToClientVpnTargetNetwork -> Maybe Bool
..} =
      forall a. Monoid a => [a] -> a
Prelude.mconcat
        [ ByteString
"Action"
            forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"ApplySecurityGroupsToClientVpnTargetNetwork" ::
                        Prelude.ByteString
                    ),
          ByteString
"Version"
            forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
          ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
          ByteString
"ClientVpnEndpointId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
clientVpnEndpointId,
          ByteString
"VpcId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
vpcId,
          forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"SecurityGroupId" [Text]
securityGroupIds
        ]

-- | /See:/ 'newApplySecurityGroupsToClientVpnTargetNetworkResponse' smart constructor.
data ApplySecurityGroupsToClientVpnTargetNetworkResponse = ApplySecurityGroupsToClientVpnTargetNetworkResponse'
  { -- | The IDs of the applied security groups.
    ApplySecurityGroupsToClientVpnTargetNetworkResponse -> Maybe [Text]
securityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    ApplySecurityGroupsToClientVpnTargetNetworkResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ApplySecurityGroupsToClientVpnTargetNetworkResponse
-> ApplySecurityGroupsToClientVpnTargetNetworkResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplySecurityGroupsToClientVpnTargetNetworkResponse
-> ApplySecurityGroupsToClientVpnTargetNetworkResponse -> Bool
$c/= :: ApplySecurityGroupsToClientVpnTargetNetworkResponse
-> ApplySecurityGroupsToClientVpnTargetNetworkResponse -> Bool
== :: ApplySecurityGroupsToClientVpnTargetNetworkResponse
-> ApplySecurityGroupsToClientVpnTargetNetworkResponse -> Bool
$c== :: ApplySecurityGroupsToClientVpnTargetNetworkResponse
-> ApplySecurityGroupsToClientVpnTargetNetworkResponse -> Bool
Prelude.Eq, ReadPrec [ApplySecurityGroupsToClientVpnTargetNetworkResponse]
ReadPrec ApplySecurityGroupsToClientVpnTargetNetworkResponse
Int -> ReadS ApplySecurityGroupsToClientVpnTargetNetworkResponse
ReadS [ApplySecurityGroupsToClientVpnTargetNetworkResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplySecurityGroupsToClientVpnTargetNetworkResponse]
$creadListPrec :: ReadPrec [ApplySecurityGroupsToClientVpnTargetNetworkResponse]
readPrec :: ReadPrec ApplySecurityGroupsToClientVpnTargetNetworkResponse
$creadPrec :: ReadPrec ApplySecurityGroupsToClientVpnTargetNetworkResponse
readList :: ReadS [ApplySecurityGroupsToClientVpnTargetNetworkResponse]
$creadList :: ReadS [ApplySecurityGroupsToClientVpnTargetNetworkResponse]
readsPrec :: Int -> ReadS ApplySecurityGroupsToClientVpnTargetNetworkResponse
$creadsPrec :: Int -> ReadS ApplySecurityGroupsToClientVpnTargetNetworkResponse
Prelude.Read, Int -> ApplySecurityGroupsToClientVpnTargetNetworkResponse -> ShowS
[ApplySecurityGroupsToClientVpnTargetNetworkResponse] -> ShowS
ApplySecurityGroupsToClientVpnTargetNetworkResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplySecurityGroupsToClientVpnTargetNetworkResponse] -> ShowS
$cshowList :: [ApplySecurityGroupsToClientVpnTargetNetworkResponse] -> ShowS
show :: ApplySecurityGroupsToClientVpnTargetNetworkResponse -> String
$cshow :: ApplySecurityGroupsToClientVpnTargetNetworkResponse -> String
showsPrec :: Int -> ApplySecurityGroupsToClientVpnTargetNetworkResponse -> ShowS
$cshowsPrec :: Int -> ApplySecurityGroupsToClientVpnTargetNetworkResponse -> ShowS
Prelude.Show, forall x.
Rep ApplySecurityGroupsToClientVpnTargetNetworkResponse x
-> ApplySecurityGroupsToClientVpnTargetNetworkResponse
forall x.
ApplySecurityGroupsToClientVpnTargetNetworkResponse
-> Rep ApplySecurityGroupsToClientVpnTargetNetworkResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ApplySecurityGroupsToClientVpnTargetNetworkResponse x
-> ApplySecurityGroupsToClientVpnTargetNetworkResponse
$cfrom :: forall x.
ApplySecurityGroupsToClientVpnTargetNetworkResponse
-> Rep ApplySecurityGroupsToClientVpnTargetNetworkResponse x
Prelude.Generic)

-- |
-- Create a value of 'ApplySecurityGroupsToClientVpnTargetNetworkResponse' 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:
--
-- 'securityGroupIds', 'applySecurityGroupsToClientVpnTargetNetworkResponse_securityGroupIds' - The IDs of the applied security groups.
--
-- 'httpStatus', 'applySecurityGroupsToClientVpnTargetNetworkResponse_httpStatus' - The response's http status code.
newApplySecurityGroupsToClientVpnTargetNetworkResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ApplySecurityGroupsToClientVpnTargetNetworkResponse
newApplySecurityGroupsToClientVpnTargetNetworkResponse :: Int -> ApplySecurityGroupsToClientVpnTargetNetworkResponse
newApplySecurityGroupsToClientVpnTargetNetworkResponse
  Int
pHttpStatus_ =
    ApplySecurityGroupsToClientVpnTargetNetworkResponse'
      { $sel:securityGroupIds:ApplySecurityGroupsToClientVpnTargetNetworkResponse' :: Maybe [Text]
securityGroupIds =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ApplySecurityGroupsToClientVpnTargetNetworkResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

-- | The IDs of the applied security groups.
applySecurityGroupsToClientVpnTargetNetworkResponse_securityGroupIds :: Lens.Lens' ApplySecurityGroupsToClientVpnTargetNetworkResponse (Prelude.Maybe [Prelude.Text])
applySecurityGroupsToClientVpnTargetNetworkResponse_securityGroupIds :: Lens'
  ApplySecurityGroupsToClientVpnTargetNetworkResponse (Maybe [Text])
applySecurityGroupsToClientVpnTargetNetworkResponse_securityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ApplySecurityGroupsToClientVpnTargetNetworkResponse' {Maybe [Text]
securityGroupIds :: Maybe [Text]
$sel:securityGroupIds:ApplySecurityGroupsToClientVpnTargetNetworkResponse' :: ApplySecurityGroupsToClientVpnTargetNetworkResponse -> Maybe [Text]
securityGroupIds} -> Maybe [Text]
securityGroupIds) (\s :: ApplySecurityGroupsToClientVpnTargetNetworkResponse
s@ApplySecurityGroupsToClientVpnTargetNetworkResponse' {} Maybe [Text]
a -> ApplySecurityGroupsToClientVpnTargetNetworkResponse
s {$sel:securityGroupIds:ApplySecurityGroupsToClientVpnTargetNetworkResponse' :: Maybe [Text]
securityGroupIds = Maybe [Text]
a} :: ApplySecurityGroupsToClientVpnTargetNetworkResponse) 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 response's http status code.
applySecurityGroupsToClientVpnTargetNetworkResponse_httpStatus :: Lens.Lens' ApplySecurityGroupsToClientVpnTargetNetworkResponse Prelude.Int
applySecurityGroupsToClientVpnTargetNetworkResponse_httpStatus :: Lens' ApplySecurityGroupsToClientVpnTargetNetworkResponse Int
applySecurityGroupsToClientVpnTargetNetworkResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ApplySecurityGroupsToClientVpnTargetNetworkResponse' {Int
httpStatus :: Int
$sel:httpStatus:ApplySecurityGroupsToClientVpnTargetNetworkResponse' :: ApplySecurityGroupsToClientVpnTargetNetworkResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ApplySecurityGroupsToClientVpnTargetNetworkResponse
s@ApplySecurityGroupsToClientVpnTargetNetworkResponse' {} Int
a -> ApplySecurityGroupsToClientVpnTargetNetworkResponse
s {$sel:httpStatus:ApplySecurityGroupsToClientVpnTargetNetworkResponse' :: Int
httpStatus = Int
a} :: ApplySecurityGroupsToClientVpnTargetNetworkResponse)

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