{-# 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.ElasticSearch.AuthorizeVpcEndpointAccess
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides access to an Amazon OpenSearch Service domain through the use
-- of an interface VPC endpoint.
module Amazonka.ElasticSearch.AuthorizeVpcEndpointAccess
  ( -- * Creating a Request
    AuthorizeVpcEndpointAccess (..),
    newAuthorizeVpcEndpointAccess,

    -- * Request Lenses
    authorizeVpcEndpointAccess_domainName,
    authorizeVpcEndpointAccess_account,

    -- * Destructuring the Response
    AuthorizeVpcEndpointAccessResponse (..),
    newAuthorizeVpcEndpointAccessResponse,

    -- * Response Lenses
    authorizeVpcEndpointAccessResponse_httpStatus,
    authorizeVpcEndpointAccessResponse_authorizedPrincipal,
  )
where

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

-- | Container for request parameters to the @AuthorizeVpcEndpointAccess@
-- operation. Specifies the account to be permitted to manage VPC endpoints
-- against the domain.
--
-- /See:/ 'newAuthorizeVpcEndpointAccess' smart constructor.
data AuthorizeVpcEndpointAccess = AuthorizeVpcEndpointAccess'
  { -- | The name of the OpenSearch Service domain to provide access to.
    AuthorizeVpcEndpointAccess -> Text
domainName :: Prelude.Text,
    -- | The account ID to grant access to.
    AuthorizeVpcEndpointAccess -> Text
account :: Prelude.Text
  }
  deriving (AuthorizeVpcEndpointAccess -> AuthorizeVpcEndpointAccess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthorizeVpcEndpointAccess -> AuthorizeVpcEndpointAccess -> Bool
$c/= :: AuthorizeVpcEndpointAccess -> AuthorizeVpcEndpointAccess -> Bool
== :: AuthorizeVpcEndpointAccess -> AuthorizeVpcEndpointAccess -> Bool
$c== :: AuthorizeVpcEndpointAccess -> AuthorizeVpcEndpointAccess -> Bool
Prelude.Eq, ReadPrec [AuthorizeVpcEndpointAccess]
ReadPrec AuthorizeVpcEndpointAccess
Int -> ReadS AuthorizeVpcEndpointAccess
ReadS [AuthorizeVpcEndpointAccess]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AuthorizeVpcEndpointAccess]
$creadListPrec :: ReadPrec [AuthorizeVpcEndpointAccess]
readPrec :: ReadPrec AuthorizeVpcEndpointAccess
$creadPrec :: ReadPrec AuthorizeVpcEndpointAccess
readList :: ReadS [AuthorizeVpcEndpointAccess]
$creadList :: ReadS [AuthorizeVpcEndpointAccess]
readsPrec :: Int -> ReadS AuthorizeVpcEndpointAccess
$creadsPrec :: Int -> ReadS AuthorizeVpcEndpointAccess
Prelude.Read, Int -> AuthorizeVpcEndpointAccess -> ShowS
[AuthorizeVpcEndpointAccess] -> ShowS
AuthorizeVpcEndpointAccess -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthorizeVpcEndpointAccess] -> ShowS
$cshowList :: [AuthorizeVpcEndpointAccess] -> ShowS
show :: AuthorizeVpcEndpointAccess -> String
$cshow :: AuthorizeVpcEndpointAccess -> String
showsPrec :: Int -> AuthorizeVpcEndpointAccess -> ShowS
$cshowsPrec :: Int -> AuthorizeVpcEndpointAccess -> ShowS
Prelude.Show, forall x.
Rep AuthorizeVpcEndpointAccess x -> AuthorizeVpcEndpointAccess
forall x.
AuthorizeVpcEndpointAccess -> Rep AuthorizeVpcEndpointAccess x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AuthorizeVpcEndpointAccess x -> AuthorizeVpcEndpointAccess
$cfrom :: forall x.
AuthorizeVpcEndpointAccess -> Rep AuthorizeVpcEndpointAccess x
Prelude.Generic)

-- |
-- Create a value of 'AuthorizeVpcEndpointAccess' 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:
--
-- 'domainName', 'authorizeVpcEndpointAccess_domainName' - The name of the OpenSearch Service domain to provide access to.
--
-- 'account', 'authorizeVpcEndpointAccess_account' - The account ID to grant access to.
newAuthorizeVpcEndpointAccess ::
  -- | 'domainName'
  Prelude.Text ->
  -- | 'account'
  Prelude.Text ->
  AuthorizeVpcEndpointAccess
newAuthorizeVpcEndpointAccess :: Text -> Text -> AuthorizeVpcEndpointAccess
newAuthorizeVpcEndpointAccess Text
pDomainName_ Text
pAccount_ =
  AuthorizeVpcEndpointAccess'
    { $sel:domainName:AuthorizeVpcEndpointAccess' :: Text
domainName =
        Text
pDomainName_,
      $sel:account:AuthorizeVpcEndpointAccess' :: Text
account = Text
pAccount_
    }

-- | The name of the OpenSearch Service domain to provide access to.
authorizeVpcEndpointAccess_domainName :: Lens.Lens' AuthorizeVpcEndpointAccess Prelude.Text
authorizeVpcEndpointAccess_domainName :: Lens' AuthorizeVpcEndpointAccess Text
authorizeVpcEndpointAccess_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeVpcEndpointAccess' {Text
domainName :: Text
$sel:domainName:AuthorizeVpcEndpointAccess' :: AuthorizeVpcEndpointAccess -> Text
domainName} -> Text
domainName) (\s :: AuthorizeVpcEndpointAccess
s@AuthorizeVpcEndpointAccess' {} Text
a -> AuthorizeVpcEndpointAccess
s {$sel:domainName:AuthorizeVpcEndpointAccess' :: Text
domainName = Text
a} :: AuthorizeVpcEndpointAccess)

-- | The account ID to grant access to.
authorizeVpcEndpointAccess_account :: Lens.Lens' AuthorizeVpcEndpointAccess Prelude.Text
authorizeVpcEndpointAccess_account :: Lens' AuthorizeVpcEndpointAccess Text
authorizeVpcEndpointAccess_account = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeVpcEndpointAccess' {Text
account :: Text
$sel:account:AuthorizeVpcEndpointAccess' :: AuthorizeVpcEndpointAccess -> Text
account} -> Text
account) (\s :: AuthorizeVpcEndpointAccess
s@AuthorizeVpcEndpointAccess' {} Text
a -> AuthorizeVpcEndpointAccess
s {$sel:account:AuthorizeVpcEndpointAccess' :: Text
account = Text
a} :: AuthorizeVpcEndpointAccess)

instance Core.AWSRequest AuthorizeVpcEndpointAccess where
  type
    AWSResponse AuthorizeVpcEndpointAccess =
      AuthorizeVpcEndpointAccessResponse
  request :: (Service -> Service)
-> AuthorizeVpcEndpointAccess -> Request AuthorizeVpcEndpointAccess
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy AuthorizeVpcEndpointAccess
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AuthorizeVpcEndpointAccess)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Int -> AuthorizedPrincipal -> AuthorizeVpcEndpointAccessResponse
AuthorizeVpcEndpointAccessResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"AuthorizedPrincipal")
      )

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

instance Prelude.NFData AuthorizeVpcEndpointAccess where
  rnf :: AuthorizeVpcEndpointAccess -> ()
rnf AuthorizeVpcEndpointAccess' {Text
account :: Text
domainName :: Text
$sel:account:AuthorizeVpcEndpointAccess' :: AuthorizeVpcEndpointAccess -> Text
$sel:domainName:AuthorizeVpcEndpointAccess' :: AuthorizeVpcEndpointAccess -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
domainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
account

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

instance Data.ToJSON AuthorizeVpcEndpointAccess where
  toJSON :: AuthorizeVpcEndpointAccess -> Value
toJSON AuthorizeVpcEndpointAccess' {Text
account :: Text
domainName :: Text
$sel:account:AuthorizeVpcEndpointAccess' :: AuthorizeVpcEndpointAccess -> Text
$sel:domainName:AuthorizeVpcEndpointAccess' :: AuthorizeVpcEndpointAccess -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"Account" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
account)]
      )

instance Data.ToPath AuthorizeVpcEndpointAccess where
  toPath :: AuthorizeVpcEndpointAccess -> ByteString
toPath AuthorizeVpcEndpointAccess' {Text
account :: Text
domainName :: Text
$sel:account:AuthorizeVpcEndpointAccess' :: AuthorizeVpcEndpointAccess -> Text
$sel:domainName:AuthorizeVpcEndpointAccess' :: AuthorizeVpcEndpointAccess -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/2015-01-01/es/domain/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
domainName,
        ByteString
"/authorizeVpcEndpointAccess"
      ]

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

-- | Container for response parameters to the @AuthorizeVpcEndpointAccess@
-- operation. Contains the account ID and the type of the account being
-- authorized to access the VPC endpoint.
--
-- /See:/ 'newAuthorizeVpcEndpointAccessResponse' smart constructor.
data AuthorizeVpcEndpointAccessResponse = AuthorizeVpcEndpointAccessResponse'
  { -- | The response's http status code.
    AuthorizeVpcEndpointAccessResponse -> Int
httpStatus :: Prelude.Int,
    -- | Information about the account or service that was provided access to the
    -- domain.
    AuthorizeVpcEndpointAccessResponse -> AuthorizedPrincipal
authorizedPrincipal :: AuthorizedPrincipal
  }
  deriving (AuthorizeVpcEndpointAccessResponse
-> AuthorizeVpcEndpointAccessResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthorizeVpcEndpointAccessResponse
-> AuthorizeVpcEndpointAccessResponse -> Bool
$c/= :: AuthorizeVpcEndpointAccessResponse
-> AuthorizeVpcEndpointAccessResponse -> Bool
== :: AuthorizeVpcEndpointAccessResponse
-> AuthorizeVpcEndpointAccessResponse -> Bool
$c== :: AuthorizeVpcEndpointAccessResponse
-> AuthorizeVpcEndpointAccessResponse -> Bool
Prelude.Eq, ReadPrec [AuthorizeVpcEndpointAccessResponse]
ReadPrec AuthorizeVpcEndpointAccessResponse
Int -> ReadS AuthorizeVpcEndpointAccessResponse
ReadS [AuthorizeVpcEndpointAccessResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AuthorizeVpcEndpointAccessResponse]
$creadListPrec :: ReadPrec [AuthorizeVpcEndpointAccessResponse]
readPrec :: ReadPrec AuthorizeVpcEndpointAccessResponse
$creadPrec :: ReadPrec AuthorizeVpcEndpointAccessResponse
readList :: ReadS [AuthorizeVpcEndpointAccessResponse]
$creadList :: ReadS [AuthorizeVpcEndpointAccessResponse]
readsPrec :: Int -> ReadS AuthorizeVpcEndpointAccessResponse
$creadsPrec :: Int -> ReadS AuthorizeVpcEndpointAccessResponse
Prelude.Read, Int -> AuthorizeVpcEndpointAccessResponse -> ShowS
[AuthorizeVpcEndpointAccessResponse] -> ShowS
AuthorizeVpcEndpointAccessResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthorizeVpcEndpointAccessResponse] -> ShowS
$cshowList :: [AuthorizeVpcEndpointAccessResponse] -> ShowS
show :: AuthorizeVpcEndpointAccessResponse -> String
$cshow :: AuthorizeVpcEndpointAccessResponse -> String
showsPrec :: Int -> AuthorizeVpcEndpointAccessResponse -> ShowS
$cshowsPrec :: Int -> AuthorizeVpcEndpointAccessResponse -> ShowS
Prelude.Show, forall x.
Rep AuthorizeVpcEndpointAccessResponse x
-> AuthorizeVpcEndpointAccessResponse
forall x.
AuthorizeVpcEndpointAccessResponse
-> Rep AuthorizeVpcEndpointAccessResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AuthorizeVpcEndpointAccessResponse x
-> AuthorizeVpcEndpointAccessResponse
$cfrom :: forall x.
AuthorizeVpcEndpointAccessResponse
-> Rep AuthorizeVpcEndpointAccessResponse x
Prelude.Generic)

-- |
-- Create a value of 'AuthorizeVpcEndpointAccessResponse' 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:
--
-- 'httpStatus', 'authorizeVpcEndpointAccessResponse_httpStatus' - The response's http status code.
--
-- 'authorizedPrincipal', 'authorizeVpcEndpointAccessResponse_authorizedPrincipal' - Information about the account or service that was provided access to the
-- domain.
newAuthorizeVpcEndpointAccessResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'authorizedPrincipal'
  AuthorizedPrincipal ->
  AuthorizeVpcEndpointAccessResponse
newAuthorizeVpcEndpointAccessResponse :: Int -> AuthorizedPrincipal -> AuthorizeVpcEndpointAccessResponse
newAuthorizeVpcEndpointAccessResponse
  Int
pHttpStatus_
  AuthorizedPrincipal
pAuthorizedPrincipal_ =
    AuthorizeVpcEndpointAccessResponse'
      { $sel:httpStatus:AuthorizeVpcEndpointAccessResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:authorizedPrincipal:AuthorizeVpcEndpointAccessResponse' :: AuthorizedPrincipal
authorizedPrincipal =
          AuthorizedPrincipal
pAuthorizedPrincipal_
      }

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

-- | Information about the account or service that was provided access to the
-- domain.
authorizeVpcEndpointAccessResponse_authorizedPrincipal :: Lens.Lens' AuthorizeVpcEndpointAccessResponse AuthorizedPrincipal
authorizeVpcEndpointAccessResponse_authorizedPrincipal :: Lens' AuthorizeVpcEndpointAccessResponse AuthorizedPrincipal
authorizeVpcEndpointAccessResponse_authorizedPrincipal = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeVpcEndpointAccessResponse' {AuthorizedPrincipal
authorizedPrincipal :: AuthorizedPrincipal
$sel:authorizedPrincipal:AuthorizeVpcEndpointAccessResponse' :: AuthorizeVpcEndpointAccessResponse -> AuthorizedPrincipal
authorizedPrincipal} -> AuthorizedPrincipal
authorizedPrincipal) (\s :: AuthorizeVpcEndpointAccessResponse
s@AuthorizeVpcEndpointAccessResponse' {} AuthorizedPrincipal
a -> AuthorizeVpcEndpointAccessResponse
s {$sel:authorizedPrincipal:AuthorizeVpcEndpointAccessResponse' :: AuthorizedPrincipal
authorizedPrincipal = AuthorizedPrincipal
a} :: AuthorizeVpcEndpointAccessResponse)

instance
  Prelude.NFData
    AuthorizeVpcEndpointAccessResponse
  where
  rnf :: AuthorizeVpcEndpointAccessResponse -> ()
rnf AuthorizeVpcEndpointAccessResponse' {Int
AuthorizedPrincipal
authorizedPrincipal :: AuthorizedPrincipal
httpStatus :: Int
$sel:authorizedPrincipal:AuthorizeVpcEndpointAccessResponse' :: AuthorizeVpcEndpointAccessResponse -> AuthorizedPrincipal
$sel:httpStatus:AuthorizeVpcEndpointAccessResponse' :: AuthorizeVpcEndpointAccessResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AuthorizedPrincipal
authorizedPrincipal