{-# 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.DeleteOutboundCrossClusterSearchConnection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Allows the source domain owner to delete an existing outbound
-- cross-cluster search connection.
module Amazonka.ElasticSearch.DeleteOutboundCrossClusterSearchConnection
  ( -- * Creating a Request
    DeleteOutboundCrossClusterSearchConnection (..),
    newDeleteOutboundCrossClusterSearchConnection,

    -- * Request Lenses
    deleteOutboundCrossClusterSearchConnection_crossClusterSearchConnectionId,

    -- * Destructuring the Response
    DeleteOutboundCrossClusterSearchConnectionResponse (..),
    newDeleteOutboundCrossClusterSearchConnectionResponse,

    -- * Response Lenses
    deleteOutboundCrossClusterSearchConnectionResponse_crossClusterSearchConnection,
    deleteOutboundCrossClusterSearchConnectionResponse_httpStatus,
  )
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 the parameters to the
-- @DeleteOutboundCrossClusterSearchConnection@ operation.
--
-- /See:/ 'newDeleteOutboundCrossClusterSearchConnection' smart constructor.
data DeleteOutboundCrossClusterSearchConnection = DeleteOutboundCrossClusterSearchConnection'
  { -- | The id of the outbound connection that you want to permanently delete.
    DeleteOutboundCrossClusterSearchConnection -> Text
crossClusterSearchConnectionId :: Prelude.Text
  }
  deriving (DeleteOutboundCrossClusterSearchConnection
-> DeleteOutboundCrossClusterSearchConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteOutboundCrossClusterSearchConnection
-> DeleteOutboundCrossClusterSearchConnection -> Bool
$c/= :: DeleteOutboundCrossClusterSearchConnection
-> DeleteOutboundCrossClusterSearchConnection -> Bool
== :: DeleteOutboundCrossClusterSearchConnection
-> DeleteOutboundCrossClusterSearchConnection -> Bool
$c== :: DeleteOutboundCrossClusterSearchConnection
-> DeleteOutboundCrossClusterSearchConnection -> Bool
Prelude.Eq, ReadPrec [DeleteOutboundCrossClusterSearchConnection]
ReadPrec DeleteOutboundCrossClusterSearchConnection
Int -> ReadS DeleteOutboundCrossClusterSearchConnection
ReadS [DeleteOutboundCrossClusterSearchConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteOutboundCrossClusterSearchConnection]
$creadListPrec :: ReadPrec [DeleteOutboundCrossClusterSearchConnection]
readPrec :: ReadPrec DeleteOutboundCrossClusterSearchConnection
$creadPrec :: ReadPrec DeleteOutboundCrossClusterSearchConnection
readList :: ReadS [DeleteOutboundCrossClusterSearchConnection]
$creadList :: ReadS [DeleteOutboundCrossClusterSearchConnection]
readsPrec :: Int -> ReadS DeleteOutboundCrossClusterSearchConnection
$creadsPrec :: Int -> ReadS DeleteOutboundCrossClusterSearchConnection
Prelude.Read, Int -> DeleteOutboundCrossClusterSearchConnection -> ShowS
[DeleteOutboundCrossClusterSearchConnection] -> ShowS
DeleteOutboundCrossClusterSearchConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteOutboundCrossClusterSearchConnection] -> ShowS
$cshowList :: [DeleteOutboundCrossClusterSearchConnection] -> ShowS
show :: DeleteOutboundCrossClusterSearchConnection -> String
$cshow :: DeleteOutboundCrossClusterSearchConnection -> String
showsPrec :: Int -> DeleteOutboundCrossClusterSearchConnection -> ShowS
$cshowsPrec :: Int -> DeleteOutboundCrossClusterSearchConnection -> ShowS
Prelude.Show, forall x.
Rep DeleteOutboundCrossClusterSearchConnection x
-> DeleteOutboundCrossClusterSearchConnection
forall x.
DeleteOutboundCrossClusterSearchConnection
-> Rep DeleteOutboundCrossClusterSearchConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteOutboundCrossClusterSearchConnection x
-> DeleteOutboundCrossClusterSearchConnection
$cfrom :: forall x.
DeleteOutboundCrossClusterSearchConnection
-> Rep DeleteOutboundCrossClusterSearchConnection x
Prelude.Generic)

-- |
-- Create a value of 'DeleteOutboundCrossClusterSearchConnection' 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:
--
-- 'crossClusterSearchConnectionId', 'deleteOutboundCrossClusterSearchConnection_crossClusterSearchConnectionId' - The id of the outbound connection that you want to permanently delete.
newDeleteOutboundCrossClusterSearchConnection ::
  -- | 'crossClusterSearchConnectionId'
  Prelude.Text ->
  DeleteOutboundCrossClusterSearchConnection
newDeleteOutboundCrossClusterSearchConnection :: Text -> DeleteOutboundCrossClusterSearchConnection
newDeleteOutboundCrossClusterSearchConnection
  Text
pCrossClusterSearchConnectionId_ =
    DeleteOutboundCrossClusterSearchConnection'
      { $sel:crossClusterSearchConnectionId:DeleteOutboundCrossClusterSearchConnection' :: Text
crossClusterSearchConnectionId =
          Text
pCrossClusterSearchConnectionId_
      }

-- | The id of the outbound connection that you want to permanently delete.
deleteOutboundCrossClusterSearchConnection_crossClusterSearchConnectionId :: Lens.Lens' DeleteOutboundCrossClusterSearchConnection Prelude.Text
deleteOutboundCrossClusterSearchConnection_crossClusterSearchConnectionId :: Lens' DeleteOutboundCrossClusterSearchConnection Text
deleteOutboundCrossClusterSearchConnection_crossClusterSearchConnectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteOutboundCrossClusterSearchConnection' {Text
crossClusterSearchConnectionId :: Text
$sel:crossClusterSearchConnectionId:DeleteOutboundCrossClusterSearchConnection' :: DeleteOutboundCrossClusterSearchConnection -> Text
crossClusterSearchConnectionId} -> Text
crossClusterSearchConnectionId) (\s :: DeleteOutboundCrossClusterSearchConnection
s@DeleteOutboundCrossClusterSearchConnection' {} Text
a -> DeleteOutboundCrossClusterSearchConnection
s {$sel:crossClusterSearchConnectionId:DeleteOutboundCrossClusterSearchConnection' :: Text
crossClusterSearchConnectionId = Text
a} :: DeleteOutboundCrossClusterSearchConnection)

instance
  Core.AWSRequest
    DeleteOutboundCrossClusterSearchConnection
  where
  type
    AWSResponse
      DeleteOutboundCrossClusterSearchConnection =
      DeleteOutboundCrossClusterSearchConnectionResponse
  request :: (Service -> Service)
-> DeleteOutboundCrossClusterSearchConnection
-> Request DeleteOutboundCrossClusterSearchConnection
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteOutboundCrossClusterSearchConnection
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse DeleteOutboundCrossClusterSearchConnection)))
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 ->
          Maybe OutboundCrossClusterSearchConnection
-> Int -> DeleteOutboundCrossClusterSearchConnectionResponse
DeleteOutboundCrossClusterSearchConnectionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CrossClusterSearchConnection")
            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
    DeleteOutboundCrossClusterSearchConnection
  where
  hashWithSalt :: Int -> DeleteOutboundCrossClusterSearchConnection -> Int
hashWithSalt
    Int
_salt
    DeleteOutboundCrossClusterSearchConnection' {Text
crossClusterSearchConnectionId :: Text
$sel:crossClusterSearchConnectionId:DeleteOutboundCrossClusterSearchConnection' :: DeleteOutboundCrossClusterSearchConnection -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
crossClusterSearchConnectionId

instance
  Prelude.NFData
    DeleteOutboundCrossClusterSearchConnection
  where
  rnf :: DeleteOutboundCrossClusterSearchConnection -> ()
rnf DeleteOutboundCrossClusterSearchConnection' {Text
crossClusterSearchConnectionId :: Text
$sel:crossClusterSearchConnectionId:DeleteOutboundCrossClusterSearchConnection' :: DeleteOutboundCrossClusterSearchConnection -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
crossClusterSearchConnectionId

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

instance
  Data.ToPath
    DeleteOutboundCrossClusterSearchConnection
  where
  toPath :: DeleteOutboundCrossClusterSearchConnection -> ByteString
toPath
    DeleteOutboundCrossClusterSearchConnection' {Text
crossClusterSearchConnectionId :: Text
$sel:crossClusterSearchConnectionId:DeleteOutboundCrossClusterSearchConnection' :: DeleteOutboundCrossClusterSearchConnection -> Text
..} =
      forall a. Monoid a => [a] -> a
Prelude.mconcat
        [ ByteString
"/2015-01-01/es/ccs/outboundConnection/",
          forall a. ToByteString a => a -> ByteString
Data.toBS Text
crossClusterSearchConnectionId
        ]

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

-- | The result of a @DeleteOutboundCrossClusterSearchConnection@ operation.
-- Contains details of deleted outbound connection.
--
-- /See:/ 'newDeleteOutboundCrossClusterSearchConnectionResponse' smart constructor.
data DeleteOutboundCrossClusterSearchConnectionResponse = DeleteOutboundCrossClusterSearchConnectionResponse'
  { -- | Specifies the @OutboundCrossClusterSearchConnection@ of deleted outbound
    -- connection.
    DeleteOutboundCrossClusterSearchConnectionResponse
-> Maybe OutboundCrossClusterSearchConnection
crossClusterSearchConnection :: Prelude.Maybe OutboundCrossClusterSearchConnection,
    -- | The response's http status code.
    DeleteOutboundCrossClusterSearchConnectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteOutboundCrossClusterSearchConnectionResponse
-> DeleteOutboundCrossClusterSearchConnectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteOutboundCrossClusterSearchConnectionResponse
-> DeleteOutboundCrossClusterSearchConnectionResponse -> Bool
$c/= :: DeleteOutboundCrossClusterSearchConnectionResponse
-> DeleteOutboundCrossClusterSearchConnectionResponse -> Bool
== :: DeleteOutboundCrossClusterSearchConnectionResponse
-> DeleteOutboundCrossClusterSearchConnectionResponse -> Bool
$c== :: DeleteOutboundCrossClusterSearchConnectionResponse
-> DeleteOutboundCrossClusterSearchConnectionResponse -> Bool
Prelude.Eq, ReadPrec [DeleteOutboundCrossClusterSearchConnectionResponse]
ReadPrec DeleteOutboundCrossClusterSearchConnectionResponse
Int -> ReadS DeleteOutboundCrossClusterSearchConnectionResponse
ReadS [DeleteOutboundCrossClusterSearchConnectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteOutboundCrossClusterSearchConnectionResponse]
$creadListPrec :: ReadPrec [DeleteOutboundCrossClusterSearchConnectionResponse]
readPrec :: ReadPrec DeleteOutboundCrossClusterSearchConnectionResponse
$creadPrec :: ReadPrec DeleteOutboundCrossClusterSearchConnectionResponse
readList :: ReadS [DeleteOutboundCrossClusterSearchConnectionResponse]
$creadList :: ReadS [DeleteOutboundCrossClusterSearchConnectionResponse]
readsPrec :: Int -> ReadS DeleteOutboundCrossClusterSearchConnectionResponse
$creadsPrec :: Int -> ReadS DeleteOutboundCrossClusterSearchConnectionResponse
Prelude.Read, Int -> DeleteOutboundCrossClusterSearchConnectionResponse -> ShowS
[DeleteOutboundCrossClusterSearchConnectionResponse] -> ShowS
DeleteOutboundCrossClusterSearchConnectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteOutboundCrossClusterSearchConnectionResponse] -> ShowS
$cshowList :: [DeleteOutboundCrossClusterSearchConnectionResponse] -> ShowS
show :: DeleteOutboundCrossClusterSearchConnectionResponse -> String
$cshow :: DeleteOutboundCrossClusterSearchConnectionResponse -> String
showsPrec :: Int -> DeleteOutboundCrossClusterSearchConnectionResponse -> ShowS
$cshowsPrec :: Int -> DeleteOutboundCrossClusterSearchConnectionResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteOutboundCrossClusterSearchConnectionResponse x
-> DeleteOutboundCrossClusterSearchConnectionResponse
forall x.
DeleteOutboundCrossClusterSearchConnectionResponse
-> Rep DeleteOutboundCrossClusterSearchConnectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteOutboundCrossClusterSearchConnectionResponse x
-> DeleteOutboundCrossClusterSearchConnectionResponse
$cfrom :: forall x.
DeleteOutboundCrossClusterSearchConnectionResponse
-> Rep DeleteOutboundCrossClusterSearchConnectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteOutboundCrossClusterSearchConnectionResponse' 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:
--
-- 'crossClusterSearchConnection', 'deleteOutboundCrossClusterSearchConnectionResponse_crossClusterSearchConnection' - Specifies the @OutboundCrossClusterSearchConnection@ of deleted outbound
-- connection.
--
-- 'httpStatus', 'deleteOutboundCrossClusterSearchConnectionResponse_httpStatus' - The response's http status code.
newDeleteOutboundCrossClusterSearchConnectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteOutboundCrossClusterSearchConnectionResponse
newDeleteOutboundCrossClusterSearchConnectionResponse :: Int -> DeleteOutboundCrossClusterSearchConnectionResponse
newDeleteOutboundCrossClusterSearchConnectionResponse
  Int
pHttpStatus_ =
    DeleteOutboundCrossClusterSearchConnectionResponse'
      { $sel:crossClusterSearchConnection:DeleteOutboundCrossClusterSearchConnectionResponse' :: Maybe OutboundCrossClusterSearchConnection
crossClusterSearchConnection =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DeleteOutboundCrossClusterSearchConnectionResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

-- | Specifies the @OutboundCrossClusterSearchConnection@ of deleted outbound
-- connection.
deleteOutboundCrossClusterSearchConnectionResponse_crossClusterSearchConnection :: Lens.Lens' DeleteOutboundCrossClusterSearchConnectionResponse (Prelude.Maybe OutboundCrossClusterSearchConnection)
deleteOutboundCrossClusterSearchConnectionResponse_crossClusterSearchConnection :: Lens'
  DeleteOutboundCrossClusterSearchConnectionResponse
  (Maybe OutboundCrossClusterSearchConnection)
deleteOutboundCrossClusterSearchConnectionResponse_crossClusterSearchConnection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteOutboundCrossClusterSearchConnectionResponse' {Maybe OutboundCrossClusterSearchConnection
crossClusterSearchConnection :: Maybe OutboundCrossClusterSearchConnection
$sel:crossClusterSearchConnection:DeleteOutboundCrossClusterSearchConnectionResponse' :: DeleteOutboundCrossClusterSearchConnectionResponse
-> Maybe OutboundCrossClusterSearchConnection
crossClusterSearchConnection} -> Maybe OutboundCrossClusterSearchConnection
crossClusterSearchConnection) (\s :: DeleteOutboundCrossClusterSearchConnectionResponse
s@DeleteOutboundCrossClusterSearchConnectionResponse' {} Maybe OutboundCrossClusterSearchConnection
a -> DeleteOutboundCrossClusterSearchConnectionResponse
s {$sel:crossClusterSearchConnection:DeleteOutboundCrossClusterSearchConnectionResponse' :: Maybe OutboundCrossClusterSearchConnection
crossClusterSearchConnection = Maybe OutboundCrossClusterSearchConnection
a} :: DeleteOutboundCrossClusterSearchConnectionResponse)

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

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