{-# 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.Redshift.ModifyEndpointAccess
-- 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 a Redshift-managed VPC endpoint.
module Amazonka.Redshift.ModifyEndpointAccess
  ( -- * Creating a Request
    ModifyEndpointAccess (..),
    newModifyEndpointAccess,

    -- * Request Lenses
    modifyEndpointAccess_vpcSecurityGroupIds,
    modifyEndpointAccess_endpointName,

    -- * Destructuring the Response
    EndpointAccess (..),
    newEndpointAccess,

    -- * Response Lenses
    endpointAccess_address,
    endpointAccess_clusterIdentifier,
    endpointAccess_endpointCreateTime,
    endpointAccess_endpointName,
    endpointAccess_endpointStatus,
    endpointAccess_port,
    endpointAccess_resourceOwner,
    endpointAccess_subnetGroupName,
    endpointAccess_vpcEndpoint,
    endpointAccess_vpcSecurityGroups,
  )
where

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 Amazonka.Redshift.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newModifyEndpointAccess' smart constructor.
data ModifyEndpointAccess = ModifyEndpointAccess'
  { -- | The complete list of VPC security groups associated with the endpoint
    -- after the endpoint is modified.
    ModifyEndpointAccess -> Maybe [Text]
vpcSecurityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | The endpoint to be modified.
    ModifyEndpointAccess -> Text
endpointName :: Prelude.Text
  }
  deriving (ModifyEndpointAccess -> ModifyEndpointAccess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyEndpointAccess -> ModifyEndpointAccess -> Bool
$c/= :: ModifyEndpointAccess -> ModifyEndpointAccess -> Bool
== :: ModifyEndpointAccess -> ModifyEndpointAccess -> Bool
$c== :: ModifyEndpointAccess -> ModifyEndpointAccess -> Bool
Prelude.Eq, ReadPrec [ModifyEndpointAccess]
ReadPrec ModifyEndpointAccess
Int -> ReadS ModifyEndpointAccess
ReadS [ModifyEndpointAccess]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyEndpointAccess]
$creadListPrec :: ReadPrec [ModifyEndpointAccess]
readPrec :: ReadPrec ModifyEndpointAccess
$creadPrec :: ReadPrec ModifyEndpointAccess
readList :: ReadS [ModifyEndpointAccess]
$creadList :: ReadS [ModifyEndpointAccess]
readsPrec :: Int -> ReadS ModifyEndpointAccess
$creadsPrec :: Int -> ReadS ModifyEndpointAccess
Prelude.Read, Int -> ModifyEndpointAccess -> ShowS
[ModifyEndpointAccess] -> ShowS
ModifyEndpointAccess -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyEndpointAccess] -> ShowS
$cshowList :: [ModifyEndpointAccess] -> ShowS
show :: ModifyEndpointAccess -> String
$cshow :: ModifyEndpointAccess -> String
showsPrec :: Int -> ModifyEndpointAccess -> ShowS
$cshowsPrec :: Int -> ModifyEndpointAccess -> ShowS
Prelude.Show, forall x. Rep ModifyEndpointAccess x -> ModifyEndpointAccess
forall x. ModifyEndpointAccess -> Rep ModifyEndpointAccess x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModifyEndpointAccess x -> ModifyEndpointAccess
$cfrom :: forall x. ModifyEndpointAccess -> Rep ModifyEndpointAccess x
Prelude.Generic)

-- |
-- Create a value of 'ModifyEndpointAccess' 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:
--
-- 'vpcSecurityGroupIds', 'modifyEndpointAccess_vpcSecurityGroupIds' - The complete list of VPC security groups associated with the endpoint
-- after the endpoint is modified.
--
-- 'endpointName', 'modifyEndpointAccess_endpointName' - The endpoint to be modified.
newModifyEndpointAccess ::
  -- | 'endpointName'
  Prelude.Text ->
  ModifyEndpointAccess
newModifyEndpointAccess :: Text -> ModifyEndpointAccess
newModifyEndpointAccess Text
pEndpointName_ =
  ModifyEndpointAccess'
    { $sel:vpcSecurityGroupIds:ModifyEndpointAccess' :: Maybe [Text]
vpcSecurityGroupIds =
        forall a. Maybe a
Prelude.Nothing,
      $sel:endpointName:ModifyEndpointAccess' :: Text
endpointName = Text
pEndpointName_
    }

-- | The complete list of VPC security groups associated with the endpoint
-- after the endpoint is modified.
modifyEndpointAccess_vpcSecurityGroupIds :: Lens.Lens' ModifyEndpointAccess (Prelude.Maybe [Prelude.Text])
modifyEndpointAccess_vpcSecurityGroupIds :: Lens' ModifyEndpointAccess (Maybe [Text])
modifyEndpointAccess_vpcSecurityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyEndpointAccess' {Maybe [Text]
vpcSecurityGroupIds :: Maybe [Text]
$sel:vpcSecurityGroupIds:ModifyEndpointAccess' :: ModifyEndpointAccess -> Maybe [Text]
vpcSecurityGroupIds} -> Maybe [Text]
vpcSecurityGroupIds) (\s :: ModifyEndpointAccess
s@ModifyEndpointAccess' {} Maybe [Text]
a -> ModifyEndpointAccess
s {$sel:vpcSecurityGroupIds:ModifyEndpointAccess' :: Maybe [Text]
vpcSecurityGroupIds = Maybe [Text]
a} :: ModifyEndpointAccess) 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 endpoint to be modified.
modifyEndpointAccess_endpointName :: Lens.Lens' ModifyEndpointAccess Prelude.Text
modifyEndpointAccess_endpointName :: Lens' ModifyEndpointAccess Text
modifyEndpointAccess_endpointName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyEndpointAccess' {Text
endpointName :: Text
$sel:endpointName:ModifyEndpointAccess' :: ModifyEndpointAccess -> Text
endpointName} -> Text
endpointName) (\s :: ModifyEndpointAccess
s@ModifyEndpointAccess' {} Text
a -> ModifyEndpointAccess
s {$sel:endpointName:ModifyEndpointAccess' :: Text
endpointName = Text
a} :: ModifyEndpointAccess)

instance Core.AWSRequest ModifyEndpointAccess where
  type
    AWSResponse ModifyEndpointAccess =
      EndpointAccess
  request :: (Service -> Service)
-> ModifyEndpointAccess -> Request ModifyEndpointAccess
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 ModifyEndpointAccess
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ModifyEndpointAccess)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"ModifyEndpointAccessResult"
      (\Int
s ResponseHeaders
h [Node]
x -> forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)

instance Prelude.Hashable ModifyEndpointAccess where
  hashWithSalt :: Int -> ModifyEndpointAccess -> Int
hashWithSalt Int
_salt ModifyEndpointAccess' {Maybe [Text]
Text
endpointName :: Text
vpcSecurityGroupIds :: Maybe [Text]
$sel:endpointName:ModifyEndpointAccess' :: ModifyEndpointAccess -> Text
$sel:vpcSecurityGroupIds:ModifyEndpointAccess' :: ModifyEndpointAccess -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
vpcSecurityGroupIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointName

instance Prelude.NFData ModifyEndpointAccess where
  rnf :: ModifyEndpointAccess -> ()
rnf ModifyEndpointAccess' {Maybe [Text]
Text
endpointName :: Text
vpcSecurityGroupIds :: Maybe [Text]
$sel:endpointName:ModifyEndpointAccess' :: ModifyEndpointAccess -> Text
$sel:vpcSecurityGroupIds:ModifyEndpointAccess' :: ModifyEndpointAccess -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
vpcSecurityGroupIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
endpointName

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

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

instance Data.ToQuery ModifyEndpointAccess where
  toQuery :: ModifyEndpointAccess -> QueryString
toQuery ModifyEndpointAccess' {Maybe [Text]
Text
endpointName :: Text
vpcSecurityGroupIds :: Maybe [Text]
$sel:endpointName:ModifyEndpointAccess' :: ModifyEndpointAccess -> Text
$sel:vpcSecurityGroupIds:ModifyEndpointAccess' :: ModifyEndpointAccess -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ModifyEndpointAccess" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: Prelude.ByteString),
        ByteString
"VpcSecurityGroupIds"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"VpcSecurityGroupId"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
vpcSecurityGroupIds
            ),
        ByteString
"EndpointName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
endpointName
      ]