{-# 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.ModifyVerifiedAccessEndpoint
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies the configuration of an Amazon Web Services Verified Access
-- endpoint.
module Amazonka.EC2.ModifyVerifiedAccessEndpoint
  ( -- * Creating a Request
    ModifyVerifiedAccessEndpoint (..),
    newModifyVerifiedAccessEndpoint,

    -- * Request Lenses
    modifyVerifiedAccessEndpoint_clientToken,
    modifyVerifiedAccessEndpoint_description,
    modifyVerifiedAccessEndpoint_dryRun,
    modifyVerifiedAccessEndpoint_loadBalancerOptions,
    modifyVerifiedAccessEndpoint_networkInterfaceOptions,
    modifyVerifiedAccessEndpoint_verifiedAccessGroupId,
    modifyVerifiedAccessEndpoint_verifiedAccessEndpointId,

    -- * Destructuring the Response
    ModifyVerifiedAccessEndpointResponse (..),
    newModifyVerifiedAccessEndpointResponse,

    -- * Response Lenses
    modifyVerifiedAccessEndpointResponse_verifiedAccessEndpoint,
    modifyVerifiedAccessEndpointResponse_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:/ 'newModifyVerifiedAccessEndpoint' smart constructor.
data ModifyVerifiedAccessEndpoint = ModifyVerifiedAccessEndpoint'
  { -- | A unique, case-sensitive token that you provide to ensure idempotency of
    -- your modification request. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/Run_Instance_Idempotency.html Ensuring Idempotency>.
    ModifyVerifiedAccessEndpoint -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | A description for the Amazon Web Services Verified Access endpoint.
    ModifyVerifiedAccessEndpoint -> Maybe Text
description :: 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@.
    ModifyVerifiedAccessEndpoint -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The load balancer details if creating the Amazon Web Services Verified
    -- Access endpoint as @load-balancer@type.
    ModifyVerifiedAccessEndpoint
-> Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
loadBalancerOptions :: Prelude.Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions,
    -- | The network interface options.
    ModifyVerifiedAccessEndpoint
-> Maybe ModifyVerifiedAccessEndpointEniOptions
networkInterfaceOptions :: Prelude.Maybe ModifyVerifiedAccessEndpointEniOptions,
    -- | The ID of the Amazon Web Services Verified Access group.
    ModifyVerifiedAccessEndpoint -> Maybe Text
verifiedAccessGroupId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Amazon Web Services Verified Access endpoint.
    ModifyVerifiedAccessEndpoint -> Text
verifiedAccessEndpointId :: Prelude.Text
  }
  deriving (ModifyVerifiedAccessEndpoint
-> ModifyVerifiedAccessEndpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyVerifiedAccessEndpoint
-> ModifyVerifiedAccessEndpoint -> Bool
$c/= :: ModifyVerifiedAccessEndpoint
-> ModifyVerifiedAccessEndpoint -> Bool
== :: ModifyVerifiedAccessEndpoint
-> ModifyVerifiedAccessEndpoint -> Bool
$c== :: ModifyVerifiedAccessEndpoint
-> ModifyVerifiedAccessEndpoint -> Bool
Prelude.Eq, ReadPrec [ModifyVerifiedAccessEndpoint]
ReadPrec ModifyVerifiedAccessEndpoint
Int -> ReadS ModifyVerifiedAccessEndpoint
ReadS [ModifyVerifiedAccessEndpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyVerifiedAccessEndpoint]
$creadListPrec :: ReadPrec [ModifyVerifiedAccessEndpoint]
readPrec :: ReadPrec ModifyVerifiedAccessEndpoint
$creadPrec :: ReadPrec ModifyVerifiedAccessEndpoint
readList :: ReadS [ModifyVerifiedAccessEndpoint]
$creadList :: ReadS [ModifyVerifiedAccessEndpoint]
readsPrec :: Int -> ReadS ModifyVerifiedAccessEndpoint
$creadsPrec :: Int -> ReadS ModifyVerifiedAccessEndpoint
Prelude.Read, Int -> ModifyVerifiedAccessEndpoint -> ShowS
[ModifyVerifiedAccessEndpoint] -> ShowS
ModifyVerifiedAccessEndpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyVerifiedAccessEndpoint] -> ShowS
$cshowList :: [ModifyVerifiedAccessEndpoint] -> ShowS
show :: ModifyVerifiedAccessEndpoint -> String
$cshow :: ModifyVerifiedAccessEndpoint -> String
showsPrec :: Int -> ModifyVerifiedAccessEndpoint -> ShowS
$cshowsPrec :: Int -> ModifyVerifiedAccessEndpoint -> ShowS
Prelude.Show, forall x.
Rep ModifyVerifiedAccessEndpoint x -> ModifyVerifiedAccessEndpoint
forall x.
ModifyVerifiedAccessEndpoint -> Rep ModifyVerifiedAccessEndpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifyVerifiedAccessEndpoint x -> ModifyVerifiedAccessEndpoint
$cfrom :: forall x.
ModifyVerifiedAccessEndpoint -> Rep ModifyVerifiedAccessEndpoint x
Prelude.Generic)

-- |
-- Create a value of 'ModifyVerifiedAccessEndpoint' 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:
--
-- 'clientToken', 'modifyVerifiedAccessEndpoint_clientToken' - A unique, case-sensitive token that you provide to ensure idempotency of
-- your modification request. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/Run_Instance_Idempotency.html Ensuring Idempotency>.
--
-- 'description', 'modifyVerifiedAccessEndpoint_description' - A description for the Amazon Web Services Verified Access endpoint.
--
-- 'dryRun', 'modifyVerifiedAccessEndpoint_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@.
--
-- 'loadBalancerOptions', 'modifyVerifiedAccessEndpoint_loadBalancerOptions' - The load balancer details if creating the Amazon Web Services Verified
-- Access endpoint as @load-balancer@type.
--
-- 'networkInterfaceOptions', 'modifyVerifiedAccessEndpoint_networkInterfaceOptions' - The network interface options.
--
-- 'verifiedAccessGroupId', 'modifyVerifiedAccessEndpoint_verifiedAccessGroupId' - The ID of the Amazon Web Services Verified Access group.
--
-- 'verifiedAccessEndpointId', 'modifyVerifiedAccessEndpoint_verifiedAccessEndpointId' - The ID of the Amazon Web Services Verified Access endpoint.
newModifyVerifiedAccessEndpoint ::
  -- | 'verifiedAccessEndpointId'
  Prelude.Text ->
  ModifyVerifiedAccessEndpoint
newModifyVerifiedAccessEndpoint :: Text -> ModifyVerifiedAccessEndpoint
newModifyVerifiedAccessEndpoint
  Text
pVerifiedAccessEndpointId_ =
    ModifyVerifiedAccessEndpoint'
      { $sel:clientToken:ModifyVerifiedAccessEndpoint' :: Maybe Text
clientToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:description:ModifyVerifiedAccessEndpoint' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:dryRun:ModifyVerifiedAccessEndpoint' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
        $sel:loadBalancerOptions:ModifyVerifiedAccessEndpoint' :: Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
loadBalancerOptions = forall a. Maybe a
Prelude.Nothing,
        $sel:networkInterfaceOptions:ModifyVerifiedAccessEndpoint' :: Maybe ModifyVerifiedAccessEndpointEniOptions
networkInterfaceOptions = forall a. Maybe a
Prelude.Nothing,
        $sel:verifiedAccessGroupId:ModifyVerifiedAccessEndpoint' :: Maybe Text
verifiedAccessGroupId = forall a. Maybe a
Prelude.Nothing,
        $sel:verifiedAccessEndpointId:ModifyVerifiedAccessEndpoint' :: Text
verifiedAccessEndpointId =
          Text
pVerifiedAccessEndpointId_
      }

-- | A unique, case-sensitive token that you provide to ensure idempotency of
-- your modification request. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/Run_Instance_Idempotency.html Ensuring Idempotency>.
modifyVerifiedAccessEndpoint_clientToken :: Lens.Lens' ModifyVerifiedAccessEndpoint (Prelude.Maybe Prelude.Text)
modifyVerifiedAccessEndpoint_clientToken :: Lens' ModifyVerifiedAccessEndpoint (Maybe Text)
modifyVerifiedAccessEndpoint_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyVerifiedAccessEndpoint' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: ModifyVerifiedAccessEndpoint
s@ModifyVerifiedAccessEndpoint' {} Maybe Text
a -> ModifyVerifiedAccessEndpoint
s {$sel:clientToken:ModifyVerifiedAccessEndpoint' :: Maybe Text
clientToken = Maybe Text
a} :: ModifyVerifiedAccessEndpoint)

-- | A description for the Amazon Web Services Verified Access endpoint.
modifyVerifiedAccessEndpoint_description :: Lens.Lens' ModifyVerifiedAccessEndpoint (Prelude.Maybe Prelude.Text)
modifyVerifiedAccessEndpoint_description :: Lens' ModifyVerifiedAccessEndpoint (Maybe Text)
modifyVerifiedAccessEndpoint_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyVerifiedAccessEndpoint' {Maybe Text
description :: Maybe Text
$sel:description:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
description} -> Maybe Text
description) (\s :: ModifyVerifiedAccessEndpoint
s@ModifyVerifiedAccessEndpoint' {} Maybe Text
a -> ModifyVerifiedAccessEndpoint
s {$sel:description:ModifyVerifiedAccessEndpoint' :: Maybe Text
description = Maybe Text
a} :: ModifyVerifiedAccessEndpoint)

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

-- | The load balancer details if creating the Amazon Web Services Verified
-- Access endpoint as @load-balancer@type.
modifyVerifiedAccessEndpoint_loadBalancerOptions :: Lens.Lens' ModifyVerifiedAccessEndpoint (Prelude.Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions)
modifyVerifiedAccessEndpoint_loadBalancerOptions :: Lens'
  ModifyVerifiedAccessEndpoint
  (Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions)
modifyVerifiedAccessEndpoint_loadBalancerOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyVerifiedAccessEndpoint' {Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
loadBalancerOptions :: Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
$sel:loadBalancerOptions:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint
-> Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
loadBalancerOptions} -> Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
loadBalancerOptions) (\s :: ModifyVerifiedAccessEndpoint
s@ModifyVerifiedAccessEndpoint' {} Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
a -> ModifyVerifiedAccessEndpoint
s {$sel:loadBalancerOptions:ModifyVerifiedAccessEndpoint' :: Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
loadBalancerOptions = Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
a} :: ModifyVerifiedAccessEndpoint)

-- | The network interface options.
modifyVerifiedAccessEndpoint_networkInterfaceOptions :: Lens.Lens' ModifyVerifiedAccessEndpoint (Prelude.Maybe ModifyVerifiedAccessEndpointEniOptions)
modifyVerifiedAccessEndpoint_networkInterfaceOptions :: Lens'
  ModifyVerifiedAccessEndpoint
  (Maybe ModifyVerifiedAccessEndpointEniOptions)
modifyVerifiedAccessEndpoint_networkInterfaceOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyVerifiedAccessEndpoint' {Maybe ModifyVerifiedAccessEndpointEniOptions
networkInterfaceOptions :: Maybe ModifyVerifiedAccessEndpointEniOptions
$sel:networkInterfaceOptions:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint
-> Maybe ModifyVerifiedAccessEndpointEniOptions
networkInterfaceOptions} -> Maybe ModifyVerifiedAccessEndpointEniOptions
networkInterfaceOptions) (\s :: ModifyVerifiedAccessEndpoint
s@ModifyVerifiedAccessEndpoint' {} Maybe ModifyVerifiedAccessEndpointEniOptions
a -> ModifyVerifiedAccessEndpoint
s {$sel:networkInterfaceOptions:ModifyVerifiedAccessEndpoint' :: Maybe ModifyVerifiedAccessEndpointEniOptions
networkInterfaceOptions = Maybe ModifyVerifiedAccessEndpointEniOptions
a} :: ModifyVerifiedAccessEndpoint)

-- | The ID of the Amazon Web Services Verified Access group.
modifyVerifiedAccessEndpoint_verifiedAccessGroupId :: Lens.Lens' ModifyVerifiedAccessEndpoint (Prelude.Maybe Prelude.Text)
modifyVerifiedAccessEndpoint_verifiedAccessGroupId :: Lens' ModifyVerifiedAccessEndpoint (Maybe Text)
modifyVerifiedAccessEndpoint_verifiedAccessGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyVerifiedAccessEndpoint' {Maybe Text
verifiedAccessGroupId :: Maybe Text
$sel:verifiedAccessGroupId:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
verifiedAccessGroupId} -> Maybe Text
verifiedAccessGroupId) (\s :: ModifyVerifiedAccessEndpoint
s@ModifyVerifiedAccessEndpoint' {} Maybe Text
a -> ModifyVerifiedAccessEndpoint
s {$sel:verifiedAccessGroupId:ModifyVerifiedAccessEndpoint' :: Maybe Text
verifiedAccessGroupId = Maybe Text
a} :: ModifyVerifiedAccessEndpoint)

-- | The ID of the Amazon Web Services Verified Access endpoint.
modifyVerifiedAccessEndpoint_verifiedAccessEndpointId :: Lens.Lens' ModifyVerifiedAccessEndpoint Prelude.Text
modifyVerifiedAccessEndpoint_verifiedAccessEndpointId :: Lens' ModifyVerifiedAccessEndpoint Text
modifyVerifiedAccessEndpoint_verifiedAccessEndpointId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyVerifiedAccessEndpoint' {Text
verifiedAccessEndpointId :: Text
$sel:verifiedAccessEndpointId:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Text
verifiedAccessEndpointId} -> Text
verifiedAccessEndpointId) (\s :: ModifyVerifiedAccessEndpoint
s@ModifyVerifiedAccessEndpoint' {} Text
a -> ModifyVerifiedAccessEndpoint
s {$sel:verifiedAccessEndpointId:ModifyVerifiedAccessEndpoint' :: Text
verifiedAccessEndpointId = Text
a} :: ModifyVerifiedAccessEndpoint)

instance Core.AWSRequest ModifyVerifiedAccessEndpoint where
  type
    AWSResponse ModifyVerifiedAccessEndpoint =
      ModifyVerifiedAccessEndpointResponse
  request :: (Service -> Service)
-> ModifyVerifiedAccessEndpoint
-> Request ModifyVerifiedAccessEndpoint
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 ModifyVerifiedAccessEndpoint
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ModifyVerifiedAccessEndpoint)))
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 VerifiedAccessEndpoint
-> Int -> ModifyVerifiedAccessEndpointResponse
ModifyVerifiedAccessEndpointResponse'
            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
"verifiedAccessEndpoint")
            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
    ModifyVerifiedAccessEndpoint
  where
  hashWithSalt :: Int -> ModifyVerifiedAccessEndpoint -> Int
hashWithSalt Int
_salt ModifyVerifiedAccessEndpoint' {Maybe Bool
Maybe Text
Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
Maybe ModifyVerifiedAccessEndpointEniOptions
Text
verifiedAccessEndpointId :: Text
verifiedAccessGroupId :: Maybe Text
networkInterfaceOptions :: Maybe ModifyVerifiedAccessEndpointEniOptions
loadBalancerOptions :: Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:verifiedAccessEndpointId:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Text
$sel:verifiedAccessGroupId:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
$sel:networkInterfaceOptions:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint
-> Maybe ModifyVerifiedAccessEndpointEniOptions
$sel:loadBalancerOptions:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint
-> Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
$sel:dryRun:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Bool
$sel:description:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
$sel:clientToken:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
loadBalancerOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModifyVerifiedAccessEndpointEniOptions
networkInterfaceOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
verifiedAccessGroupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
verifiedAccessEndpointId

instance Prelude.NFData ModifyVerifiedAccessEndpoint where
  rnf :: ModifyVerifiedAccessEndpoint -> ()
rnf ModifyVerifiedAccessEndpoint' {Maybe Bool
Maybe Text
Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
Maybe ModifyVerifiedAccessEndpointEniOptions
Text
verifiedAccessEndpointId :: Text
verifiedAccessGroupId :: Maybe Text
networkInterfaceOptions :: Maybe ModifyVerifiedAccessEndpointEniOptions
loadBalancerOptions :: Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:verifiedAccessEndpointId:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Text
$sel:verifiedAccessGroupId:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
$sel:networkInterfaceOptions:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint
-> Maybe ModifyVerifiedAccessEndpointEniOptions
$sel:loadBalancerOptions:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint
-> Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
$sel:dryRun:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Bool
$sel:description:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
$sel:clientToken:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      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 Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
loadBalancerOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModifyVerifiedAccessEndpointEniOptions
networkInterfaceOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
verifiedAccessGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
verifiedAccessEndpointId

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

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

instance Data.ToQuery ModifyVerifiedAccessEndpoint where
  toQuery :: ModifyVerifiedAccessEndpoint -> QueryString
toQuery ModifyVerifiedAccessEndpoint' {Maybe Bool
Maybe Text
Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
Maybe ModifyVerifiedAccessEndpointEniOptions
Text
verifiedAccessEndpointId :: Text
verifiedAccessGroupId :: Maybe Text
networkInterfaceOptions :: Maybe ModifyVerifiedAccessEndpointEniOptions
loadBalancerOptions :: Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:verifiedAccessEndpointId:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Text
$sel:verifiedAccessGroupId:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
$sel:networkInterfaceOptions:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint
-> Maybe ModifyVerifiedAccessEndpointEniOptions
$sel:loadBalancerOptions:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint
-> Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
$sel:dryRun:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Bool
$sel:description:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
$sel:clientToken:ModifyVerifiedAccessEndpoint' :: ModifyVerifiedAccessEndpoint -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"ModifyVerifiedAccessEndpoint" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"ClientToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
clientToken,
        ByteString
"Description" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
description,
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"LoadBalancerOptions" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ModifyVerifiedAccessEndpointLoadBalancerOptions
loadBalancerOptions,
        ByteString
"NetworkInterfaceOptions"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ModifyVerifiedAccessEndpointEniOptions
networkInterfaceOptions,
        ByteString
"VerifiedAccessGroupId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
verifiedAccessGroupId,
        ByteString
"VerifiedAccessEndpointId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
verifiedAccessEndpointId
      ]

-- | /See:/ 'newModifyVerifiedAccessEndpointResponse' smart constructor.
data ModifyVerifiedAccessEndpointResponse = ModifyVerifiedAccessEndpointResponse'
  { -- | The Amazon Web Services Verified Access endpoint details.
    ModifyVerifiedAccessEndpointResponse
-> Maybe VerifiedAccessEndpoint
verifiedAccessEndpoint :: Prelude.Maybe VerifiedAccessEndpoint,
    -- | The response's http status code.
    ModifyVerifiedAccessEndpointResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ModifyVerifiedAccessEndpointResponse
-> ModifyVerifiedAccessEndpointResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyVerifiedAccessEndpointResponse
-> ModifyVerifiedAccessEndpointResponse -> Bool
$c/= :: ModifyVerifiedAccessEndpointResponse
-> ModifyVerifiedAccessEndpointResponse -> Bool
== :: ModifyVerifiedAccessEndpointResponse
-> ModifyVerifiedAccessEndpointResponse -> Bool
$c== :: ModifyVerifiedAccessEndpointResponse
-> ModifyVerifiedAccessEndpointResponse -> Bool
Prelude.Eq, ReadPrec [ModifyVerifiedAccessEndpointResponse]
ReadPrec ModifyVerifiedAccessEndpointResponse
Int -> ReadS ModifyVerifiedAccessEndpointResponse
ReadS [ModifyVerifiedAccessEndpointResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyVerifiedAccessEndpointResponse]
$creadListPrec :: ReadPrec [ModifyVerifiedAccessEndpointResponse]
readPrec :: ReadPrec ModifyVerifiedAccessEndpointResponse
$creadPrec :: ReadPrec ModifyVerifiedAccessEndpointResponse
readList :: ReadS [ModifyVerifiedAccessEndpointResponse]
$creadList :: ReadS [ModifyVerifiedAccessEndpointResponse]
readsPrec :: Int -> ReadS ModifyVerifiedAccessEndpointResponse
$creadsPrec :: Int -> ReadS ModifyVerifiedAccessEndpointResponse
Prelude.Read, Int -> ModifyVerifiedAccessEndpointResponse -> ShowS
[ModifyVerifiedAccessEndpointResponse] -> ShowS
ModifyVerifiedAccessEndpointResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyVerifiedAccessEndpointResponse] -> ShowS
$cshowList :: [ModifyVerifiedAccessEndpointResponse] -> ShowS
show :: ModifyVerifiedAccessEndpointResponse -> String
$cshow :: ModifyVerifiedAccessEndpointResponse -> String
showsPrec :: Int -> ModifyVerifiedAccessEndpointResponse -> ShowS
$cshowsPrec :: Int -> ModifyVerifiedAccessEndpointResponse -> ShowS
Prelude.Show, forall x.
Rep ModifyVerifiedAccessEndpointResponse x
-> ModifyVerifiedAccessEndpointResponse
forall x.
ModifyVerifiedAccessEndpointResponse
-> Rep ModifyVerifiedAccessEndpointResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifyVerifiedAccessEndpointResponse x
-> ModifyVerifiedAccessEndpointResponse
$cfrom :: forall x.
ModifyVerifiedAccessEndpointResponse
-> Rep ModifyVerifiedAccessEndpointResponse x
Prelude.Generic)

-- |
-- Create a value of 'ModifyVerifiedAccessEndpointResponse' 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:
--
-- 'verifiedAccessEndpoint', 'modifyVerifiedAccessEndpointResponse_verifiedAccessEndpoint' - The Amazon Web Services Verified Access endpoint details.
--
-- 'httpStatus', 'modifyVerifiedAccessEndpointResponse_httpStatus' - The response's http status code.
newModifyVerifiedAccessEndpointResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ModifyVerifiedAccessEndpointResponse
newModifyVerifiedAccessEndpointResponse :: Int -> ModifyVerifiedAccessEndpointResponse
newModifyVerifiedAccessEndpointResponse Int
pHttpStatus_ =
  ModifyVerifiedAccessEndpointResponse'
    { $sel:verifiedAccessEndpoint:ModifyVerifiedAccessEndpointResponse' :: Maybe VerifiedAccessEndpoint
verifiedAccessEndpoint =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ModifyVerifiedAccessEndpointResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Web Services Verified Access endpoint details.
modifyVerifiedAccessEndpointResponse_verifiedAccessEndpoint :: Lens.Lens' ModifyVerifiedAccessEndpointResponse (Prelude.Maybe VerifiedAccessEndpoint)
modifyVerifiedAccessEndpointResponse_verifiedAccessEndpoint :: Lens'
  ModifyVerifiedAccessEndpointResponse (Maybe VerifiedAccessEndpoint)
modifyVerifiedAccessEndpointResponse_verifiedAccessEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyVerifiedAccessEndpointResponse' {Maybe VerifiedAccessEndpoint
verifiedAccessEndpoint :: Maybe VerifiedAccessEndpoint
$sel:verifiedAccessEndpoint:ModifyVerifiedAccessEndpointResponse' :: ModifyVerifiedAccessEndpointResponse
-> Maybe VerifiedAccessEndpoint
verifiedAccessEndpoint} -> Maybe VerifiedAccessEndpoint
verifiedAccessEndpoint) (\s :: ModifyVerifiedAccessEndpointResponse
s@ModifyVerifiedAccessEndpointResponse' {} Maybe VerifiedAccessEndpoint
a -> ModifyVerifiedAccessEndpointResponse
s {$sel:verifiedAccessEndpoint:ModifyVerifiedAccessEndpointResponse' :: Maybe VerifiedAccessEndpoint
verifiedAccessEndpoint = Maybe VerifiedAccessEndpoint
a} :: ModifyVerifiedAccessEndpointResponse)

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

instance
  Prelude.NFData
    ModifyVerifiedAccessEndpointResponse
  where
  rnf :: ModifyVerifiedAccessEndpointResponse -> ()
rnf ModifyVerifiedAccessEndpointResponse' {Int
Maybe VerifiedAccessEndpoint
httpStatus :: Int
verifiedAccessEndpoint :: Maybe VerifiedAccessEndpoint
$sel:httpStatus:ModifyVerifiedAccessEndpointResponse' :: ModifyVerifiedAccessEndpointResponse -> Int
$sel:verifiedAccessEndpoint:ModifyVerifiedAccessEndpointResponse' :: ModifyVerifiedAccessEndpointResponse
-> Maybe VerifiedAccessEndpoint
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe VerifiedAccessEndpoint
verifiedAccessEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus