{-# 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.OpenSearch.DeleteOutboundConnection
-- 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 Amazon OpenSearch Service domain owner to delete an
-- existing outbound cross-cluster search connection. For more information,
-- see
-- <https://docs.aws.amazon.com/opensearch-service/latest/developerguide/cross-cluster-search.html Cross-cluster search for Amazon OpenSearch Service>.
module Amazonka.OpenSearch.DeleteOutboundConnection
  ( -- * Creating a Request
    DeleteOutboundConnection (..),
    newDeleteOutboundConnection,

    -- * Request Lenses
    deleteOutboundConnection_connectionId,

    -- * Destructuring the Response
    DeleteOutboundConnectionResponse (..),
    newDeleteOutboundConnectionResponse,

    -- * Response Lenses
    deleteOutboundConnectionResponse_connection,
    deleteOutboundConnectionResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.OpenSearch.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 @DeleteOutboundConnection@
-- operation.
--
-- /See:/ 'newDeleteOutboundConnection' smart constructor.
data DeleteOutboundConnection = DeleteOutboundConnection'
  { -- | The ID of the outbound connection you want to permanently delete.
    DeleteOutboundConnection -> Text
connectionId :: Prelude.Text
  }
  deriving (DeleteOutboundConnection -> DeleteOutboundConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteOutboundConnection -> DeleteOutboundConnection -> Bool
$c/= :: DeleteOutboundConnection -> DeleteOutboundConnection -> Bool
== :: DeleteOutboundConnection -> DeleteOutboundConnection -> Bool
$c== :: DeleteOutboundConnection -> DeleteOutboundConnection -> Bool
Prelude.Eq, ReadPrec [DeleteOutboundConnection]
ReadPrec DeleteOutboundConnection
Int -> ReadS DeleteOutboundConnection
ReadS [DeleteOutboundConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteOutboundConnection]
$creadListPrec :: ReadPrec [DeleteOutboundConnection]
readPrec :: ReadPrec DeleteOutboundConnection
$creadPrec :: ReadPrec DeleteOutboundConnection
readList :: ReadS [DeleteOutboundConnection]
$creadList :: ReadS [DeleteOutboundConnection]
readsPrec :: Int -> ReadS DeleteOutboundConnection
$creadsPrec :: Int -> ReadS DeleteOutboundConnection
Prelude.Read, Int -> DeleteOutboundConnection -> ShowS
[DeleteOutboundConnection] -> ShowS
DeleteOutboundConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteOutboundConnection] -> ShowS
$cshowList :: [DeleteOutboundConnection] -> ShowS
show :: DeleteOutboundConnection -> String
$cshow :: DeleteOutboundConnection -> String
showsPrec :: Int -> DeleteOutboundConnection -> ShowS
$cshowsPrec :: Int -> DeleteOutboundConnection -> ShowS
Prelude.Show, forall x.
Rep DeleteOutboundConnection x -> DeleteOutboundConnection
forall x.
DeleteOutboundConnection -> Rep DeleteOutboundConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteOutboundConnection x -> DeleteOutboundConnection
$cfrom :: forall x.
DeleteOutboundConnection -> Rep DeleteOutboundConnection x
Prelude.Generic)

-- |
-- Create a value of 'DeleteOutboundConnection' 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:
--
-- 'connectionId', 'deleteOutboundConnection_connectionId' - The ID of the outbound connection you want to permanently delete.
newDeleteOutboundConnection ::
  -- | 'connectionId'
  Prelude.Text ->
  DeleteOutboundConnection
newDeleteOutboundConnection :: Text -> DeleteOutboundConnection
newDeleteOutboundConnection Text
pConnectionId_ =
  DeleteOutboundConnection'
    { $sel:connectionId:DeleteOutboundConnection' :: Text
connectionId =
        Text
pConnectionId_
    }

-- | The ID of the outbound connection you want to permanently delete.
deleteOutboundConnection_connectionId :: Lens.Lens' DeleteOutboundConnection Prelude.Text
deleteOutboundConnection_connectionId :: Lens' DeleteOutboundConnection Text
deleteOutboundConnection_connectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteOutboundConnection' {Text
connectionId :: Text
$sel:connectionId:DeleteOutboundConnection' :: DeleteOutboundConnection -> Text
connectionId} -> Text
connectionId) (\s :: DeleteOutboundConnection
s@DeleteOutboundConnection' {} Text
a -> DeleteOutboundConnection
s {$sel:connectionId:DeleteOutboundConnection' :: Text
connectionId = Text
a} :: DeleteOutboundConnection)

instance Core.AWSRequest DeleteOutboundConnection where
  type
    AWSResponse DeleteOutboundConnection =
      DeleteOutboundConnectionResponse
  request :: (Service -> Service)
-> DeleteOutboundConnection -> Request DeleteOutboundConnection
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 DeleteOutboundConnection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteOutboundConnection)))
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 OutboundConnection -> Int -> DeleteOutboundConnectionResponse
DeleteOutboundConnectionResponse'
            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
"Connection")
            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 DeleteOutboundConnection where
  hashWithSalt :: Int -> DeleteOutboundConnection -> Int
hashWithSalt Int
_salt DeleteOutboundConnection' {Text
connectionId :: Text
$sel:connectionId:DeleteOutboundConnection' :: DeleteOutboundConnection -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
connectionId

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

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

instance Data.ToPath DeleteOutboundConnection where
  toPath :: DeleteOutboundConnection -> ByteString
toPath DeleteOutboundConnection' {Text
connectionId :: Text
$sel:connectionId:DeleteOutboundConnection' :: DeleteOutboundConnection -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/2021-01-01/opensearch/cc/outboundConnection/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
connectionId
      ]

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

-- | Details about the deleted outbound connection.
--
-- /See:/ 'newDeleteOutboundConnectionResponse' smart constructor.
data DeleteOutboundConnectionResponse = DeleteOutboundConnectionResponse'
  { -- | The deleted inbound connection.
    DeleteOutboundConnectionResponse -> Maybe OutboundConnection
connection :: Prelude.Maybe OutboundConnection,
    -- | The response's http status code.
    DeleteOutboundConnectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteOutboundConnectionResponse
-> DeleteOutboundConnectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteOutboundConnectionResponse
-> DeleteOutboundConnectionResponse -> Bool
$c/= :: DeleteOutboundConnectionResponse
-> DeleteOutboundConnectionResponse -> Bool
== :: DeleteOutboundConnectionResponse
-> DeleteOutboundConnectionResponse -> Bool
$c== :: DeleteOutboundConnectionResponse
-> DeleteOutboundConnectionResponse -> Bool
Prelude.Eq, ReadPrec [DeleteOutboundConnectionResponse]
ReadPrec DeleteOutboundConnectionResponse
Int -> ReadS DeleteOutboundConnectionResponse
ReadS [DeleteOutboundConnectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteOutboundConnectionResponse]
$creadListPrec :: ReadPrec [DeleteOutboundConnectionResponse]
readPrec :: ReadPrec DeleteOutboundConnectionResponse
$creadPrec :: ReadPrec DeleteOutboundConnectionResponse
readList :: ReadS [DeleteOutboundConnectionResponse]
$creadList :: ReadS [DeleteOutboundConnectionResponse]
readsPrec :: Int -> ReadS DeleteOutboundConnectionResponse
$creadsPrec :: Int -> ReadS DeleteOutboundConnectionResponse
Prelude.Read, Int -> DeleteOutboundConnectionResponse -> ShowS
[DeleteOutboundConnectionResponse] -> ShowS
DeleteOutboundConnectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteOutboundConnectionResponse] -> ShowS
$cshowList :: [DeleteOutboundConnectionResponse] -> ShowS
show :: DeleteOutboundConnectionResponse -> String
$cshow :: DeleteOutboundConnectionResponse -> String
showsPrec :: Int -> DeleteOutboundConnectionResponse -> ShowS
$cshowsPrec :: Int -> DeleteOutboundConnectionResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteOutboundConnectionResponse x
-> DeleteOutboundConnectionResponse
forall x.
DeleteOutboundConnectionResponse
-> Rep DeleteOutboundConnectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteOutboundConnectionResponse x
-> DeleteOutboundConnectionResponse
$cfrom :: forall x.
DeleteOutboundConnectionResponse
-> Rep DeleteOutboundConnectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteOutboundConnectionResponse' 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:
--
-- 'connection', 'deleteOutboundConnectionResponse_connection' - The deleted inbound connection.
--
-- 'httpStatus', 'deleteOutboundConnectionResponse_httpStatus' - The response's http status code.
newDeleteOutboundConnectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteOutboundConnectionResponse
newDeleteOutboundConnectionResponse :: Int -> DeleteOutboundConnectionResponse
newDeleteOutboundConnectionResponse Int
pHttpStatus_ =
  DeleteOutboundConnectionResponse'
    { $sel:connection:DeleteOutboundConnectionResponse' :: Maybe OutboundConnection
connection =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteOutboundConnectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The deleted inbound connection.
deleteOutboundConnectionResponse_connection :: Lens.Lens' DeleteOutboundConnectionResponse (Prelude.Maybe OutboundConnection)
deleteOutboundConnectionResponse_connection :: Lens' DeleteOutboundConnectionResponse (Maybe OutboundConnection)
deleteOutboundConnectionResponse_connection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteOutboundConnectionResponse' {Maybe OutboundConnection
connection :: Maybe OutboundConnection
$sel:connection:DeleteOutboundConnectionResponse' :: DeleteOutboundConnectionResponse -> Maybe OutboundConnection
connection} -> Maybe OutboundConnection
connection) (\s :: DeleteOutboundConnectionResponse
s@DeleteOutboundConnectionResponse' {} Maybe OutboundConnection
a -> DeleteOutboundConnectionResponse
s {$sel:connection:DeleteOutboundConnectionResponse' :: Maybe OutboundConnection
connection = Maybe OutboundConnection
a} :: DeleteOutboundConnectionResponse)

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

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